-- 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 Galley.API.Public.Conversation where

import Galley.API.Create
import Galley.API.MLS.GroupInfo
import Galley.API.MLS.SubConversation
import Galley.API.MLS.Types
import Galley.API.Query
import Galley.API.Update
import Galley.App
import Imports
import Wire.API.Federation.API
import Wire.API.Routes.API
import Wire.API.Routes.Public.Galley.Conversation

conversationAPI :: API ConversationAPI GalleyEffects
conversationAPI :: API ConversationAPI GalleyEffects
conversationAPI =
  forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-unqualified-conversation" ServerT
  (Summary "Get a conversation by ID"
   :> (Until 'V3
       :> (CanThrow 'ConvNotFound
           :> (CanThrow 'ConvAccessDenied
               :> (ZLocalUser
                   :> ("conversations"
                       :> (Capture "cnv" ConvId
                           :> MultiVerb
                                'GET
                                '[JSON]
                                '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                Conversation)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get a conversation by ID"
            :> (Until 'V3
                :> (CanThrow 'ConvNotFound
                    :> (CanThrow 'ConvAccessDenied
                        :> (ZLocalUser
                            :> ("conversations"
                                :> (Capture "cnv" ConvId
                                    :> MultiVerb
                                         'GET
                                         '[JSON]
                                         '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                         Conversation))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error InternalError) r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId -> ConvId -> Sem r Conversation
getUnqualifiedConversation
    API
  (Named
     "get-unqualified-conversation"
     (Summary "Get a conversation by ID"
      :> (Until 'V3
          :> (CanThrow 'ConvNotFound
              :> (CanThrow 'ConvAccessDenied
                  :> (ZLocalUser
                      :> ("conversations"
                          :> (Capture "cnv" ConvId
                              :> MultiVerb
                                   'GET
                                   '[JSON]
                                   '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                   Conversation))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-unqualified-conversation-legalhold-alias"
        (Summary "Get a conversation by ID (Legalhold alias)"
         :> (Until 'V2
             :> (CanThrow 'ConvNotFound
                 :> (CanThrow 'ConvAccessDenied
                     :> (ZLocalUser
                         :> ("legalhold"
                             :> ("conversations"
                                 :> (Capture "cnv" ConvId
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                          Conversation))))))))
      :<|> (Named
              "get-conversation@v2"
              (Summary "Get a conversation by ID"
               :> (Until 'V3
                   :> (MakesFederatedCall 'Galley "get-conversations"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (QualifiedCapture "cnv" ConvId
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2 200 "Conversation" Conversation]
                                                Conversation))))))))
            :<|> (Named
                    "get-conversation@v5"
                    (Summary "Get a conversation by ID"
                     :> (From 'V3
                         :> (Until 'V6
                             :> (MakesFederatedCall 'Galley "get-conversations"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[VersionedRespond
                                                              'V5 200 "Conversation" Conversation]
                                                          Conversation)))))))))
                  :<|> (Named
                          "get-conversation"
                          (Summary "Get a conversation by ID"
                           :> (From 'V6
                               :> (MakesFederatedCall 'Galley "get-conversations"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> (QualifiedCapture "cnv" ConvId
                                                       :> Get '[JSON] Conversation))))))))
                        :<|> (Named
                                "get-conversation-roles"
                                (Summary "Get existing roles available for the given conversation"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (Capture "cnv" ConvId
                                                     :> ("roles"
                                                         :> Get '[JSON] ConversationRolesList)))))))
                              :<|> (Named
                                      "get-group-info"
                                      (Summary "Get MLS group information"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "query-group-info"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'MLSMissingGroupInfo
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("groupinfo"
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[MLS]
                                                                                '[Respond
                                                                                    200
                                                                                    "The group information"
                                                                                    GroupInfoData]
                                                                                GroupInfoData))))))))))
                                    :<|> (Named
                                            "list-conversation-ids-unqualified"
                                            (Summary "[deprecated] Get all local conversation IDs."
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("ids"
                                                             :> (QueryParam'
                                                                   '[Optional, Strict,
                                                                     Description
                                                                       "Conversation ID to start from (exclusive)"]
                                                                   "start"
                                                                   ConvId
                                                                 :> (QueryParam'
                                                                       '[Optional, Strict,
                                                                         Description
                                                                           "Maximum number of IDs to return"]
                                                                       "size"
                                                                       (Range 1 1000 Int32)
                                                                     :> Get
                                                                          '[JSON]
                                                                          (ConversationList
                                                                             ConvId))))))))
                                          :<|> (Named
                                                  "list-conversation-ids-v2"
                                                  (Summary "Get all conversation IDs."
                                                   :> (Until 'V3
                                                       :> (Description PaginationDocs
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list-ids"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             GetPaginatedConversationIds
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConvIdsPage)))))))
                                                :<|> (Named
                                                        "list-conversation-ids"
                                                        (Summary "Get all conversation IDs."
                                                         :> (From 'V3
                                                             :> (Description PaginationDocs
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list-ids"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   GetPaginatedConversationIds
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      ConvIdsPage)))))))
                                                      :<|> (Named
                                                              "get-conversations"
                                                              (Summary
                                                                 "Get all *local* conversations."
                                                               :> (Until 'V3
                                                                   :> (Description
                                                                         "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QueryParam'
                                                                                     '[Optional,
                                                                                       Strict,
                                                                                       Description
                                                                                         "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                                     "ids"
                                                                                     (Range
                                                                                        1
                                                                                        32
                                                                                        (CommaSeparatedList
                                                                                           ConvId))
                                                                                   :> (QueryParam'
                                                                                         '[Optional,
                                                                                           Strict,
                                                                                           Description
                                                                                             "Conversation ID to start from (exclusive)"]
                                                                                         "start"
                                                                                         ConvId
                                                                                       :> (QueryParam'
                                                                                             '[Optional,
                                                                                               Strict,
                                                                                               Description
                                                                                                 "Maximum number of conversations to return"]
                                                                                             "size"
                                                                                             (Range
                                                                                                1
                                                                                                500
                                                                                                Int32)
                                                                                           :> MultiVerb
                                                                                                'GET
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V2
                                                                                                    200
                                                                                                    "List of local conversations"
                                                                                                    (ConversationList
                                                                                                       Conversation)]
                                                                                                (ConversationList
                                                                                                   Conversation)))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v1"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (Until 'V2
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("list"
                                                                                         :> ("v2"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> Post
                                                                                                      '[JSON]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations@v2"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V2
                                                                                   :> (Until 'V3
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("list"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ListConversations
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[VersionedRespond
                                                                                                                'V2
                                                                                                                200
                                                                                                                "Conversation page"
                                                                                                                ConversationsResponse]
                                                                                                            ConversationsResponse))))))))
                                                                        :<|> (Named
                                                                                "list-conversations@v5"
                                                                                (Summary
                                                                                   "Get conversation metadata for a list of conversation ids"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "get-conversations"
                                                                                     :> (From 'V3
                                                                                         :> (Until
                                                                                               'V6
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> ("list"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ListConversations
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[VersionedRespond
                                                                                                                      'V5
                                                                                                                      200
                                                                                                                      "Conversation page"
                                                                                                                      ConversationsResponse]
                                                                                                                  ConversationsResponse))))))))
                                                                              :<|> (Named
                                                                                      "list-conversations"
                                                                                      (Summary
                                                                                         "Get conversation metadata for a list of conversation ids"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "get-conversations"
                                                                                           :> (From
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("list"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ListConversations
                                                                                                               :> Post
                                                                                                                    '[JSON]
                                                                                                                    ConversationsResponse)))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-by-reusable-code"
                                                                                            (Summary
                                                                                               "Get limited conversation information by key/code pair"
                                                                                             :> (CanThrow
                                                                                                   'CodeNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidConversationPassword
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("join"
                                                                                                                                 :> (QueryParam'
                                                                                                                                       '[Required,
                                                                                                                                         Strict]
                                                                                                                                       "key"
                                                                                                                                       Key
                                                                                                                                     :> (QueryParam'
                                                                                                                                           '[Required,
                                                                                                                                             Strict]
                                                                                                                                           "code"
                                                                                                                                           Value
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              ConversationCoverView))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (DescriptionOAuthScope
                                                                                                         'WriteConversations
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "api-version"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (Until
                                                                                                                         'V3
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                       :> (Description
                                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                             'V2
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             NewConv
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       200
                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                       Conversation),
                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       201
                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation@v3"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (DescriptionOAuthScope
                                                                                                               'WriteConversations
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "api-version"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V3
                                                                                                                             :> (Until
                                                                                                                                   'V4
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       NewConv
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V3
                                                                                                                                                                                                 200
                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V3
                                                                                                                                                                                                 201
                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                             Conversation)))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-group-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Create a new conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-not-fully-connected-backends"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-created"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (From
                                                                                                                                     'V4
                                                                                                                                   :> (Until
                                                                                                                                         'V6
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotConnected
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 NewConv
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V5
                                                                                                                                                                                                           200
                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        CreateGroupConversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V5
                                                                                                                                                                                                           201
                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-group-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a new conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "api-version"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-not-fully-connected-backends"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-created"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (From
                                                                                                                                           'V6
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotConnected
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (Description
                                                                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                             'V6
                                                                                                                                                                                                             200
                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                          CreateGroupConversation
                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                             'V6
                                                                                                                                                                                                             201
                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation@v2"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("self"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V2
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V2
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-self-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Create a self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V3
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 Conversation)]
                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                             Conversation)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-self-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Create a self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("self"
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   Conversation)]
                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                               Conversation))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-mls-self-conversation@v5"
                                                                                                                                            (Summary
                                                                                                                                               "Get the user's MLS self-conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (Until
                                                                                                                                                       'V6
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("mls-self"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                              'V5
                                                                                                                                                                              200
                                                                                                                                                                              "The MLS self-conversation"
                                                                                                                                                                              Conversation]
                                                                                                                                                                          Conversation)))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-mls-self-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get the user's MLS self-conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V6
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("mls-self"
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "The MLS self-conversation"
                                                                                                                                                                                Conversation]
                                                                                                                                                                            Conversation))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get information about an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "get-sub-conversation"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSSubConvUnsupportedConvType
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'GET
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Subconversation"
                                                                                                                                                                                                          PublicSubConversation]
                                                                                                                                                                                                      PublicSubConversation)))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "leave-subconversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Leave an MLS subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "leave-sub-conversation"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSProtocolErrorTag
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSStaleMessage
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZClient
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "OK"]
                                                                                                                                                                                                                                ()))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "delete-subconversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Delete an MLS subconversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "delete-sub-conversation"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSStaleMessage
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       DeleteSubConversationRequest
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Deletion successful"
                                                                                                                                                                                                                              ()]
                                                                                                                                                                                                                          ())))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-subconversation-group-info"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get MLS group information of subconversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "query-group-info"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSMissingGroupInfo
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "subconv"
                                                                                                                                                                                                                     SubConvId
                                                                                                                                                                                                                   :> ("groupinfo"
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[MLS]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "The group information"
                                                                                                                                                                                                                                GroupInfoData]
                                                                                                                                                                                                                            GroupInfoData))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-one-to-one-conversation@v2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "api-version"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-created"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V3
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NonBindingTeam
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     200
                                                                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     201
                                                                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-one-to-one-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-created"
                                                                                                                                                                                           :> (From
                                                                                                                                                                                                 'V3
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                       200
                                                                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                       201
                                                                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V5
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[VersionedRespond
                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                                          Conversation]
                                                                                                                                                                                                                                      Conversation))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V6
                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                             'V7
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                                               MLSPublicKey)]
                                                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                                                           MLSPublicKey))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V7
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> (QueryParam
                                                                                                                                                                                                                                           "format"
                                                                                                                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                                     SomeKey)]
                                                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                                                 SomeKey))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 Invite
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "add-members-to-conversation"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V5
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "code-check"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationCode
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Valid"]
                                                                                                                                                                                                                                                                              ()))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V4
                                                                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                               'V4
                                                                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                                                                                                                          Event]
                                                                                                                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "get-code"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-unqualified-conversation"
        (Summary "Get a conversation by ID"
         :> (Until 'V3
             :> (CanThrow 'ConvNotFound
                 :> (CanThrow 'ConvAccessDenied
                     :> (ZLocalUser
                         :> ("conversations"
                             :> (Capture "cnv" ConvId
                                 :> MultiVerb
                                      'GET
                                      '[JSON]
                                      '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                      Conversation)))))))
      :<|> (Named
              "get-unqualified-conversation-legalhold-alias"
              (Summary "Get a conversation by ID (Legalhold alias)"
               :> (Until 'V2
                   :> (CanThrow 'ConvNotFound
                       :> (CanThrow 'ConvAccessDenied
                           :> (ZLocalUser
                               :> ("legalhold"
                                   :> ("conversations"
                                       :> (Capture "cnv" ConvId
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2 200 "Conversation" Conversation]
                                                Conversation))))))))
            :<|> (Named
                    "get-conversation@v2"
                    (Summary "Get a conversation by ID"
                     :> (Until 'V3
                         :> (MakesFederatedCall 'Galley "get-conversations"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> (QualifiedCapture "cnv" ConvId
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V2 200 "Conversation" Conversation]
                                                      Conversation))))))))
                  :<|> (Named
                          "get-conversation@v5"
                          (Summary "Get a conversation by ID"
                           :> (From 'V3
                               :> (Until 'V6
                                   :> (MakesFederatedCall 'Galley "get-conversations"
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[VersionedRespond
                                                                    'V5
                                                                    200
                                                                    "Conversation"
                                                                    Conversation]
                                                                Conversation)))))))))
                        :<|> (Named
                                "get-conversation"
                                (Summary "Get a conversation by ID"
                                 :> (From 'V6
                                     :> (MakesFederatedCall 'Galley "get-conversations"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> (QualifiedCapture "cnv" ConvId
                                                             :> Get '[JSON] Conversation))))))))
                              :<|> (Named
                                      "get-conversation-roles"
                                      (Summary
                                         "Get existing roles available for the given conversation"
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (Capture "cnv" ConvId
                                                           :> ("roles"
                                                               :> Get
                                                                    '[JSON]
                                                                    ConversationRolesList)))))))
                                    :<|> (Named
                                            "get-group-info"
                                            (Summary "Get MLS group information"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall 'Galley "query-group-info"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'MLSMissingGroupInfo
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture
                                                                               "cnv" ConvId
                                                                             :> ("groupinfo"
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[MLS]
                                                                                      '[Respond
                                                                                          200
                                                                                          "The group information"
                                                                                          GroupInfoData]
                                                                                      GroupInfoData))))))))))
                                          :<|> (Named
                                                  "list-conversation-ids-unqualified"
                                                  (Summary
                                                     "[deprecated] Get all local conversation IDs."
                                                   :> (Until 'V3
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("ids"
                                                                   :> (QueryParam'
                                                                         '[Optional, Strict,
                                                                           Description
                                                                             "Conversation ID to start from (exclusive)"]
                                                                         "start"
                                                                         ConvId
                                                                       :> (QueryParam'
                                                                             '[Optional, Strict,
                                                                               Description
                                                                                 "Maximum number of IDs to return"]
                                                                             "size"
                                                                             (Range 1 1000 Int32)
                                                                           :> Get
                                                                                '[JSON]
                                                                                (ConversationList
                                                                                   ConvId))))))))
                                                :<|> (Named
                                                        "list-conversation-ids-v2"
                                                        (Summary "Get all conversation IDs."
                                                         :> (Until 'V3
                                                             :> (Description PaginationDocs
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list-ids"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   GetPaginatedConversationIds
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      ConvIdsPage)))))))
                                                      :<|> (Named
                                                              "list-conversation-ids"
                                                              (Summary "Get all conversation IDs."
                                                               :> (From 'V3
                                                                   :> (Description PaginationDocs
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("list-ids"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         GetPaginatedConversationIds
                                                                                       :> Post
                                                                                            '[JSON]
                                                                                            ConvIdsPage)))))))
                                                            :<|> (Named
                                                                    "get-conversations"
                                                                    (Summary
                                                                       "Get all *local* conversations."
                                                                     :> (Until 'V3
                                                                         :> (Description
                                                                               "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (QueryParam'
                                                                                           '[Optional,
                                                                                             Strict,
                                                                                             Description
                                                                                               "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                                           "ids"
                                                                                           (Range
                                                                                              1
                                                                                              32
                                                                                              (CommaSeparatedList
                                                                                                 ConvId))
                                                                                         :> (QueryParam'
                                                                                               '[Optional,
                                                                                                 Strict,
                                                                                                 Description
                                                                                                   "Conversation ID to start from (exclusive)"]
                                                                                               "start"
                                                                                               ConvId
                                                                                             :> (QueryParam'
                                                                                                   '[Optional,
                                                                                                     Strict,
                                                                                                     Description
                                                                                                       "Maximum number of conversations to return"]
                                                                                                   "size"
                                                                                                   (Range
                                                                                                      1
                                                                                                      500
                                                                                                      Int32)
                                                                                                 :> MultiVerb
                                                                                                      'GET
                                                                                                      '[JSON]
                                                                                                      '[VersionedRespond
                                                                                                          'V2
                                                                                                          200
                                                                                                          "List of local conversations"
                                                                                                          (ConversationList
                                                                                                             Conversation)]
                                                                                                      (ConversationList
                                                                                                         Conversation)))))))))
                                                                  :<|> (Named
                                                                          "list-conversations@v1"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (Until 'V2
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("list"
                                                                                               :> ("v2"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ListConversations
                                                                                                       :> Post
                                                                                                            '[JSON]
                                                                                                            ConversationsResponse))))))))
                                                                        :<|> (Named
                                                                                "list-conversations@v2"
                                                                                (Summary
                                                                                   "Get conversation metadata for a list of conversation ids"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "get-conversations"
                                                                                     :> (From 'V2
                                                                                         :> (Until
                                                                                               'V3
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> ("list"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ListConversations
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[VersionedRespond
                                                                                                                      'V2
                                                                                                                      200
                                                                                                                      "Conversation page"
                                                                                                                      ConversationsResponse]
                                                                                                                  ConversationsResponse))))))))
                                                                              :<|> (Named
                                                                                      "list-conversations@v5"
                                                                                      (Summary
                                                                                         "Get conversation metadata for a list of conversation ids"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "get-conversations"
                                                                                           :> (From
                                                                                                 'V3
                                                                                               :> (Until
                                                                                                     'V6
                                                                                                   :> (ZLocalUser
                                                                                                       :> ("conversations"
                                                                                                           :> ("list"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ListConversations
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[VersionedRespond
                                                                                                                            'V5
                                                                                                                            200
                                                                                                                            "Conversation page"
                                                                                                                            ConversationsResponse]
                                                                                                                        ConversationsResponse))))))))
                                                                                    :<|> (Named
                                                                                            "list-conversations"
                                                                                            (Summary
                                                                                               "Get conversation metadata for a list of conversation ids"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "get-conversations"
                                                                                                 :> (From
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> ("list"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       ListConversations
                                                                                                                     :> Post
                                                                                                                          '[JSON]
                                                                                                                          ConversationsResponse)))))))
                                                                                          :<|> (Named
                                                                                                  "get-conversation-by-reusable-code"
                                                                                                  (Summary
                                                                                                     "Get limited conversation information by key/code pair"
                                                                                                   :> (CanThrow
                                                                                                         'CodeNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidConversationPassword
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'GuestLinksDisabled
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> ("conversations"
                                                                                                                                   :> ("join"
                                                                                                                                       :> (QueryParam'
                                                                                                                                             '[Required,
                                                                                                                                               Strict]
                                                                                                                                             "key"
                                                                                                                                             Key
                                                                                                                                           :> (QueryParam'
                                                                                                                                                 '[Required,
                                                                                                                                                   Strict]
                                                                                                                                                 "code"
                                                                                                                                                 Value
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    ConversationCoverView))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation@v2"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (DescriptionOAuthScope
                                                                                                               'WriteConversations
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "api-version"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (Until
                                                                                                                               'V3
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNonEmptyMemberList
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotConnected
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                             :> (Description
                                                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                   'V2
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   NewConv
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             200
                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                             Conversation),
                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             201
                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                         Conversation))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-group-conversation@v3"
                                                                                                              (Summary
                                                                                                                 "Create a new conversation"
                                                                                                               :> (DescriptionOAuthScope
                                                                                                                     'WriteConversations
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "api-version"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-created"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (From
                                                                                                                                     'V3
                                                                                                                                   :> (Until
                                                                                                                                         'V4
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotConnected
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                       :> (Description
                                                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             NewConv
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V3
                                                                                                                                                                                                       200
                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V3
                                                                                                                                                                                                       201
                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                   Conversation)))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-group-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Create a new conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "api-version"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-not-fully-connected-backends"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-created"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (From
                                                                                                                                           'V4
                                                                                                                                         :> (Until
                                                                                                                                               'V6
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNonEmptyMemberList
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotConnected
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V5
                                                                                                                                                                                                                 200
                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              CreateGroupConversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V5
                                                                                                                                                                                                                 201
                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                                                                                          CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-group-conversation"
                                                                                                                          (Summary
                                                                                                                             "Create a new conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "api-version"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-not-fully-connected-backends"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-created"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (From
                                                                                                                                                 'V6
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSNonEmptyMemberList
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotConnected
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (Description
                                                                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         NewConv
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'POST
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                   'V6
                                                                                                                                                                                                                   200
                                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                CreateGroupConversation
                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                   'V6
                                                                                                                                                                                                                   201
                                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                                   CreateGroupConversation)]
                                                                                                                                                                                                            CreateGroupConversationResponse))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-self-conversation@v2"
                                                                                                                                (Summary
                                                                                                                                   "Create a self-conversation"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("self"
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V2
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V2
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             Conversation)]
                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                         Conversation))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-self-conversation@v5"
                                                                                                                                      (Summary
                                                                                                                                         "Create a self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V3
                                                                                                                                           :> (Until
                                                                                                                                                 'V6
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("self"
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       200
                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                       Conversation),
                                                                                                                                                                  WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       201
                                                                                                                                                                       "Conversation created"
                                                                                                                                                                       Conversation)]
                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                   Conversation)))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-self-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Create a self-conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V6
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("self"
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         200
                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                         Conversation),
                                                                                                                                                                    WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         201
                                                                                                                                                                         "Conversation created"
                                                                                                                                                                         Conversation)]
                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                     Conversation))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-mls-self-conversation@v5"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get the user's MLS self-conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (Until
                                                                                                                                                             'V6
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("mls-self"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'GET
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[VersionedRespond
                                                                                                                                                                                    'V5
                                                                                                                                                                                    200
                                                                                                                                                                                    "The MLS self-conversation"
                                                                                                                                                                                    Conversation]
                                                                                                                                                                                Conversation)))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-mls-self-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get the user's MLS self-conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V6
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> ("mls-self"
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "The MLS self-conversation"
                                                                                                                                                                                      Conversation]
                                                                                                                                                                                  Conversation))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-subconversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get information about an MLS subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "get-sub-conversation"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSSubConvUnsupportedConvType
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'GET
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Subconversation"
                                                                                                                                                                                                                PublicSubConversation]
                                                                                                                                                                                                            PublicSubConversation)))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "leave-subconversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Leave an MLS subconversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "leave-sub-conversation"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSProtocolErrorTag
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSStaleMessage
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZClient
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                               "subconv"
                                                                                                                                                                                                                               SubConvId
                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "OK"]
                                                                                                                                                                                                                                      ()))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "delete-subconversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Delete an MLS subconversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "delete-sub-conversation"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MLSStaleMessage
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             DeleteSubConversationRequest
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Deletion successful"
                                                                                                                                                                                                                                    ()]
                                                                                                                                                                                                                                ())))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-subconversation-group-info"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get MLS group information of subconversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V5
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "query-group-info"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSMissingGroupInfo
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                           "subconv"
                                                                                                                                                                                                                           SubConvId
                                                                                                                                                                                                                         :> ("groupinfo"
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                  '[MLS]
                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "The group information"
                                                                                                                                                                                                                                      GroupInfoData]
                                                                                                                                                                                                                                  GroupInfoData))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-one-to-one-conversation@v2"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "api-version"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-created"
                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                     'V3
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NonBindingTeam
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 NewConv
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                           200
                                                                                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                           201
                                                                                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "create-one-to-one-conversation"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Create a 1:1 conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-created"
                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                       'V3
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NonBindingTeam
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                             200
                                                                                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                             201
                                                                                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                                                                                                         Conversation)))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V5
                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                             'V6
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[VersionedRespond
                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                                                                Conversation]
                                                                                                                                                                                                                                            Conversation))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V6
                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                   'V7
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                                     MLSPublicKey)]
                                                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                                                 MLSPublicKey))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-one-to-one-mls-conversation"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                     'V7
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                           :> (QueryParam
                                                                                                                                                                                                                                                 "format"
                                                                                                                                                                                                                                                 MLSPublicKeyFormat
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                                                                           SomeKey)]
                                                                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                                                                       SomeKey))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "add-members-to-conversation-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       Invite
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                       :> ("v2"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "add-members-to-conversation"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V5
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Join a conversation using a reusable code"
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           JoinConversationByCode
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "code-check"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Check validity of a conversation code."
                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> ("code-check"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationCode
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Valid"]
                                                                                                                                                                                                                                                                                    ()))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V4
                                                                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "create-conversation-code-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                     'V4
                                                                                                                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "remove-code-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Delete conversation code"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'DELETE
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                                                                                                                                                                Event]
                                                                                                                                                                                                                                                                                                            Event))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "get-code"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Get existing conversation code"
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "member-typing-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                                                                                    ())))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "member-typing-qualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "remove-member"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-other-member"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-unqualified-conversation-legalhold-alias" ServerT
  (Summary "Get a conversation by ID (Legalhold alias)"
   :> (Until 'V2
       :> (CanThrow 'ConvNotFound
           :> (CanThrow 'ConvAccessDenied
               :> (ZLocalUser
                   :> ("legalhold"
                       :> ("conversations"
                           :> (Capture "cnv" ConvId
                               :> MultiVerb
                                    'GET
                                    '[JSON]
                                    '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                    Conversation))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get a conversation by ID (Legalhold alias)"
            :> (Until 'V2
                :> (CanThrow 'ConvNotFound
                    :> (CanThrow 'ConvAccessDenied
                        :> (ZLocalUser
                            :> ("legalhold"
                                :> ("conversations"
                                    :> (Capture "cnv" ConvId
                                        :> MultiVerb
                                             'GET
                                             '[JSON]
                                             '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                             Conversation)))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error InternalError) r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId -> ConvId -> Sem r Conversation
getUnqualifiedConversation
    API
  (Named
     "get-unqualified-conversation-legalhold-alias"
     (Summary "Get a conversation by ID (Legalhold alias)"
      :> (Until 'V2
          :> (CanThrow 'ConvNotFound
              :> (CanThrow 'ConvAccessDenied
                  :> (ZLocalUser
                      :> ("legalhold"
                          :> ("conversations"
                              :> (Capture "cnv" ConvId
                                  :> MultiVerb
                                       'GET
                                       '[JSON]
                                       '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                       Conversation)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation@v2"
        (Summary "Get a conversation by ID"
         :> (Until 'V3
             :> (MakesFederatedCall 'Galley "get-conversations"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                          Conversation))))))))
      :<|> (Named
              "get-conversation@v5"
              (Summary "Get a conversation by ID"
               :> (From 'V3
                   :> (Until 'V6
                       :> (MakesFederatedCall 'Galley "get-conversations"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[VersionedRespond
                                                        'V5 200 "Conversation" Conversation]
                                                    Conversation)))))))))
            :<|> (Named
                    "get-conversation"
                    (Summary "Get a conversation by ID"
                     :> (From 'V6
                         :> (MakesFederatedCall 'Galley "get-conversations"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> (QualifiedCapture "cnv" ConvId
                                                 :> Get '[JSON] Conversation))))))))
                  :<|> (Named
                          "get-conversation-roles"
                          (Summary "Get existing roles available for the given conversation"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("roles"
                                                   :> Get '[JSON] ConversationRolesList)))))))
                        :<|> (Named
                                "get-group-info"
                                (Summary "Get MLS group information"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "query-group-info"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'MLSMissingGroupInfo
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("groupinfo"
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[MLS]
                                                                          '[Respond
                                                                              200
                                                                              "The group information"
                                                                              GroupInfoData]
                                                                          GroupInfoData))))))))))
                              :<|> (Named
                                      "list-conversation-ids-unqualified"
                                      (Summary "[deprecated] Get all local conversation IDs."
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("ids"
                                                       :> (QueryParam'
                                                             '[Optional, Strict,
                                                               Description
                                                                 "Conversation ID to start from (exclusive)"]
                                                             "start"
                                                             ConvId
                                                           :> (QueryParam'
                                                                 '[Optional, Strict,
                                                                   Description
                                                                     "Maximum number of IDs to return"]
                                                                 "size"
                                                                 (Range 1 1000 Int32)
                                                               :> Get
                                                                    '[JSON]
                                                                    (ConversationList ConvId))))))))
                                    :<|> (Named
                                            "list-conversation-ids-v2"
                                            (Summary "Get all conversation IDs."
                                             :> (Until 'V3
                                                 :> (Description PaginationDocs
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list-ids"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       GetPaginatedConversationIds
                                                                     :> Post
                                                                          '[JSON] ConvIdsPage)))))))
                                          :<|> (Named
                                                  "list-conversation-ids"
                                                  (Summary "Get all conversation IDs."
                                                   :> (From 'V3
                                                       :> (Description PaginationDocs
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list-ids"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             GetPaginatedConversationIds
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConvIdsPage)))))))
                                                :<|> (Named
                                                        "get-conversations"
                                                        (Summary "Get all *local* conversations."
                                                         :> (Until 'V3
                                                             :> (Description
                                                                   "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QueryParam'
                                                                               '[Optional, Strict,
                                                                                 Description
                                                                                   "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                               "ids"
                                                                               (Range
                                                                                  1
                                                                                  32
                                                                                  (CommaSeparatedList
                                                                                     ConvId))
                                                                             :> (QueryParam'
                                                                                   '[Optional,
                                                                                     Strict,
                                                                                     Description
                                                                                       "Conversation ID to start from (exclusive)"]
                                                                                   "start"
                                                                                   ConvId
                                                                                 :> (QueryParam'
                                                                                       '[Optional,
                                                                                         Strict,
                                                                                         Description
                                                                                           "Maximum number of conversations to return"]
                                                                                       "size"
                                                                                       (Range
                                                                                          1
                                                                                          500
                                                                                          Int32)
                                                                                     :> MultiVerb
                                                                                          'GET
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V2
                                                                                              200
                                                                                              "List of local conversations"
                                                                                              (ConversationList
                                                                                                 Conversation)]
                                                                                          (ConversationList
                                                                                             Conversation)))))))))
                                                      :<|> (Named
                                                              "list-conversations@v1"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (Until 'V2
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("list"
                                                                                   :> ("v2"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> Post
                                                                                                '[JSON]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v2"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V2
                                                                             :> (Until 'V3
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("list"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[VersionedRespond
                                                                                                          'V2
                                                                                                          200
                                                                                                          "Conversation page"
                                                                                                          ConversationsResponse]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations@v5"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V3
                                                                                   :> (Until 'V6
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("list"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ListConversations
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[VersionedRespond
                                                                                                                'V5
                                                                                                                200
                                                                                                                "Conversation page"
                                                                                                                ConversationsResponse]
                                                                                                            ConversationsResponse))))))))
                                                                        :<|> (Named
                                                                                "list-conversations"
                                                                                (Summary
                                                                                   "Get conversation metadata for a list of conversation ids"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "get-conversations"
                                                                                     :> (From 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("list"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ListConversations
                                                                                                         :> Post
                                                                                                              '[JSON]
                                                                                                              ConversationsResponse)))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-by-reusable-code"
                                                                                      (Summary
                                                                                         "Get limited conversation information by key/code pair"
                                                                                       :> (CanThrow
                                                                                             'CodeNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidConversationPassword
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (ZLocalUser
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("join"
                                                                                                                           :> (QueryParam'
                                                                                                                                 '[Required,
                                                                                                                                   Strict]
                                                                                                                                 "key"
                                                                                                                                 Key
                                                                                                                               :> (QueryParam'
                                                                                                                                     '[Required,
                                                                                                                                       Strict]
                                                                                                                                     "code"
                                                                                                                                     Value
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        ConversationCoverView))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (DescriptionOAuthScope
                                                                                                   'WriteConversations
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "api-version"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (Until
                                                                                                                   'V3
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                 :> (Description
                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZOptConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                       'V2
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       NewConv
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 200
                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                 Conversation),
                                                                                                                                                                            WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 201
                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                 Conversation)]
                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v3"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (DescriptionOAuthScope
                                                                                                         'WriteConversations
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "api-version"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V3
                                                                                                                       :> (Until
                                                                                                                             'V4
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                           :> (Description
                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 NewConv
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V3
                                                                                                                                                                                           200
                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                           Conversation),
                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V3
                                                                                                                                                                                           201
                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                       Conversation)))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-not-fully-connected-backends"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V4
                                                                                                                             :> (Until
                                                                                                                                   'V6
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           NewConv
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V5
                                                                                                                                                                                                     200
                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  CreateGroupConversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V5
                                                                                                                                                                                                     201
                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-group-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a new conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-not-fully-connected-backends"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-created"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (From
                                                                                                                                     'V6
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNonEmptyMemberList
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotConnected
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (Description
                                                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             NewConv
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                       200
                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    CreateGroupConversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                       201
                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                                                                CreateGroupConversationResponse))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation@v2"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("self"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V2
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V2
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V3
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("self"
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           Conversation)]
                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                       Conversation)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-self-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Create a self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("self"
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             Conversation)]
                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                         Conversation))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-mls-self-conversation@v5"
                                                                                                                                      (Summary
                                                                                                                                         "Get the user's MLS self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (Until
                                                                                                                                                 'V6
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("mls-self"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                        'V5
                                                                                                                                                                        200
                                                                                                                                                                        "The MLS self-conversation"
                                                                                                                                                                        Conversation]
                                                                                                                                                                    Conversation)))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-mls-self-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get the user's MLS self-conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V6
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("mls-self"
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "The MLS self-conversation"
                                                                                                                                                                          Conversation]
                                                                                                                                                                      Conversation))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get information about an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "get-sub-conversation"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSSubConvUnsupportedConvType
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "subconv"
                                                                                                                                                                                             SubConvId
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'GET
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Subconversation"
                                                                                                                                                                                                    PublicSubConversation]
                                                                                                                                                                                                PublicSubConversation)))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "leave-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Leave an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "leave-sub-conversation"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSProtocolErrorTag
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSStaleMessage
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZClient
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "OK"]
                                                                                                                                                                                                                          ()))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "delete-subconversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Delete an MLS subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "delete-sub-conversation"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSStaleMessage
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "subconv"
                                                                                                                                                                                                             SubConvId
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 DeleteSubConversationRequest
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Deletion successful"
                                                                                                                                                                                                                        ()]
                                                                                                                                                                                                                    ())))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-subconversation-group-info"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get MLS group information of subconversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "query-group-info"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSMissingGroupInfo
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "subconv"
                                                                                                                                                                                                               SubConvId
                                                                                                                                                                                                             :> ("groupinfo"
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[MLS]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "The group information"
                                                                                                                                                                                                                          GroupInfoData]
                                                                                                                                                                                                                      GroupInfoData))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-one-to-one-conversation@v2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create a 1:1 conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "api-version"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-created"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V3
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NonBindingTeam
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               200
                                                                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               201
                                                                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                                                                           Conversation))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-one-to-one-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-created"
                                                                                                                                                                                     :> (From
                                                                                                                                                                                           'V3
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NonBindingTeam
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                 200
                                                                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                 201
                                                                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                                                                             Conversation)))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V5
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V6
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[VersionedRespond
                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                                    Conversation]
                                                                                                                                                                                                                                Conversation))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V6
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V7
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                                         MLSPublicKey)]
                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                     MLSPublicKey))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V7
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> (QueryParam
                                                                                                                                                                                                                                     "format"
                                                                                                                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                                               SomeKey)]
                                                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                                                           SomeKey))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           Invite
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "add-members-to-conversation"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V5
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "code-check"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> ("code-check"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationCode
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Valid"]
                                                                                                                                                                                                                                                                        ()))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V4
                                                                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                         'V4
                                                                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                                                                                                                    Event]
                                                                                                                                                                                                                                                                                                Event))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "get-code"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-unqualified-conversation-legalhold-alias"
        (Summary "Get a conversation by ID (Legalhold alias)"
         :> (Until 'V2
             :> (CanThrow 'ConvNotFound
                 :> (CanThrow 'ConvAccessDenied
                     :> (ZLocalUser
                         :> ("legalhold"
                             :> ("conversations"
                                 :> (Capture "cnv" ConvId
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                          Conversation))))))))
      :<|> (Named
              "get-conversation@v2"
              (Summary "Get a conversation by ID"
               :> (Until 'V3
                   :> (MakesFederatedCall 'Galley "get-conversations"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (QualifiedCapture "cnv" ConvId
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2 200 "Conversation" Conversation]
                                                Conversation))))))))
            :<|> (Named
                    "get-conversation@v5"
                    (Summary "Get a conversation by ID"
                     :> (From 'V3
                         :> (Until 'V6
                             :> (MakesFederatedCall 'Galley "get-conversations"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[VersionedRespond
                                                              'V5 200 "Conversation" Conversation]
                                                          Conversation)))))))))
                  :<|> (Named
                          "get-conversation"
                          (Summary "Get a conversation by ID"
                           :> (From 'V6
                               :> (MakesFederatedCall 'Galley "get-conversations"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> (QualifiedCapture "cnv" ConvId
                                                       :> Get '[JSON] Conversation))))))))
                        :<|> (Named
                                "get-conversation-roles"
                                (Summary "Get existing roles available for the given conversation"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (Capture "cnv" ConvId
                                                     :> ("roles"
                                                         :> Get '[JSON] ConversationRolesList)))))))
                              :<|> (Named
                                      "get-group-info"
                                      (Summary "Get MLS group information"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "query-group-info"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'MLSMissingGroupInfo
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("groupinfo"
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[MLS]
                                                                                '[Respond
                                                                                    200
                                                                                    "The group information"
                                                                                    GroupInfoData]
                                                                                GroupInfoData))))))))))
                                    :<|> (Named
                                            "list-conversation-ids-unqualified"
                                            (Summary "[deprecated] Get all local conversation IDs."
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("ids"
                                                             :> (QueryParam'
                                                                   '[Optional, Strict,
                                                                     Description
                                                                       "Conversation ID to start from (exclusive)"]
                                                                   "start"
                                                                   ConvId
                                                                 :> (QueryParam'
                                                                       '[Optional, Strict,
                                                                         Description
                                                                           "Maximum number of IDs to return"]
                                                                       "size"
                                                                       (Range 1 1000 Int32)
                                                                     :> Get
                                                                          '[JSON]
                                                                          (ConversationList
                                                                             ConvId))))))))
                                          :<|> (Named
                                                  "list-conversation-ids-v2"
                                                  (Summary "Get all conversation IDs."
                                                   :> (Until 'V3
                                                       :> (Description PaginationDocs
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list-ids"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             GetPaginatedConversationIds
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConvIdsPage)))))))
                                                :<|> (Named
                                                        "list-conversation-ids"
                                                        (Summary "Get all conversation IDs."
                                                         :> (From 'V3
                                                             :> (Description PaginationDocs
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list-ids"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   GetPaginatedConversationIds
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      ConvIdsPage)))))))
                                                      :<|> (Named
                                                              "get-conversations"
                                                              (Summary
                                                                 "Get all *local* conversations."
                                                               :> (Until 'V3
                                                                   :> (Description
                                                                         "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QueryParam'
                                                                                     '[Optional,
                                                                                       Strict,
                                                                                       Description
                                                                                         "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                                     "ids"
                                                                                     (Range
                                                                                        1
                                                                                        32
                                                                                        (CommaSeparatedList
                                                                                           ConvId))
                                                                                   :> (QueryParam'
                                                                                         '[Optional,
                                                                                           Strict,
                                                                                           Description
                                                                                             "Conversation ID to start from (exclusive)"]
                                                                                         "start"
                                                                                         ConvId
                                                                                       :> (QueryParam'
                                                                                             '[Optional,
                                                                                               Strict,
                                                                                               Description
                                                                                                 "Maximum number of conversations to return"]
                                                                                             "size"
                                                                                             (Range
                                                                                                1
                                                                                                500
                                                                                                Int32)
                                                                                           :> MultiVerb
                                                                                                'GET
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V2
                                                                                                    200
                                                                                                    "List of local conversations"
                                                                                                    (ConversationList
                                                                                                       Conversation)]
                                                                                                (ConversationList
                                                                                                   Conversation)))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v1"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (Until 'V2
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("list"
                                                                                         :> ("v2"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> Post
                                                                                                      '[JSON]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations@v2"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V2
                                                                                   :> (Until 'V3
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("list"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ListConversations
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[VersionedRespond
                                                                                                                'V2
                                                                                                                200
                                                                                                                "Conversation page"
                                                                                                                ConversationsResponse]
                                                                                                            ConversationsResponse))))))))
                                                                        :<|> (Named
                                                                                "list-conversations@v5"
                                                                                (Summary
                                                                                   "Get conversation metadata for a list of conversation ids"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "get-conversations"
                                                                                     :> (From 'V3
                                                                                         :> (Until
                                                                                               'V6
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> ("list"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ListConversations
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[VersionedRespond
                                                                                                                      'V5
                                                                                                                      200
                                                                                                                      "Conversation page"
                                                                                                                      ConversationsResponse]
                                                                                                                  ConversationsResponse))))))))
                                                                              :<|> (Named
                                                                                      "list-conversations"
                                                                                      (Summary
                                                                                         "Get conversation metadata for a list of conversation ids"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "get-conversations"
                                                                                           :> (From
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("list"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ListConversations
                                                                                                               :> Post
                                                                                                                    '[JSON]
                                                                                                                    ConversationsResponse)))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-by-reusable-code"
                                                                                            (Summary
                                                                                               "Get limited conversation information by key/code pair"
                                                                                             :> (CanThrow
                                                                                                   'CodeNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidConversationPassword
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("join"
                                                                                                                                 :> (QueryParam'
                                                                                                                                       '[Required,
                                                                                                                                         Strict]
                                                                                                                                       "key"
                                                                                                                                       Key
                                                                                                                                     :> (QueryParam'
                                                                                                                                           '[Required,
                                                                                                                                             Strict]
                                                                                                                                           "code"
                                                                                                                                           Value
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              ConversationCoverView))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (DescriptionOAuthScope
                                                                                                         'WriteConversations
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "api-version"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (Until
                                                                                                                         'V3
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                       :> (Description
                                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                             'V2
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             NewConv
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       200
                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                       Conversation),
                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       201
                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation@v3"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (DescriptionOAuthScope
                                                                                                               'WriteConversations
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "api-version"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V3
                                                                                                                             :> (Until
                                                                                                                                   'V4
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       NewConv
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V3
                                                                                                                                                                                                 200
                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V3
                                                                                                                                                                                                 201
                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                             Conversation)))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-group-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Create a new conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-not-fully-connected-backends"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-created"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (From
                                                                                                                                     'V4
                                                                                                                                   :> (Until
                                                                                                                                         'V6
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotConnected
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 NewConv
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V5
                                                                                                                                                                                                           200
                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        CreateGroupConversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V5
                                                                                                                                                                                                           201
                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-group-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a new conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "api-version"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-not-fully-connected-backends"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-created"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (From
                                                                                                                                           'V6
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotConnected
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (Description
                                                                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                             'V6
                                                                                                                                                                                                             200
                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                          CreateGroupConversation
                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                             'V6
                                                                                                                                                                                                             201
                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation@v2"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("self"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V2
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V2
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-self-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Create a self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V3
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 Conversation)]
                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                             Conversation)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-self-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Create a self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("self"
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   Conversation)]
                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                               Conversation))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-mls-self-conversation@v5"
                                                                                                                                            (Summary
                                                                                                                                               "Get the user's MLS self-conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (Until
                                                                                                                                                       'V6
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("mls-self"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                              'V5
                                                                                                                                                                              200
                                                                                                                                                                              "The MLS self-conversation"
                                                                                                                                                                              Conversation]
                                                                                                                                                                          Conversation)))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-mls-self-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get the user's MLS self-conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V6
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("mls-self"
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "The MLS self-conversation"
                                                                                                                                                                                Conversation]
                                                                                                                                                                            Conversation))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get information about an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "get-sub-conversation"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSSubConvUnsupportedConvType
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'GET
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Subconversation"
                                                                                                                                                                                                          PublicSubConversation]
                                                                                                                                                                                                      PublicSubConversation)))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "leave-subconversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Leave an MLS subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "leave-sub-conversation"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSProtocolErrorTag
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSStaleMessage
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZClient
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "OK"]
                                                                                                                                                                                                                                ()))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "delete-subconversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Delete an MLS subconversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "delete-sub-conversation"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSStaleMessage
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       DeleteSubConversationRequest
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Deletion successful"
                                                                                                                                                                                                                              ()]
                                                                                                                                                                                                                          ())))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-subconversation-group-info"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get MLS group information of subconversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "query-group-info"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSMissingGroupInfo
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                     "subconv"
                                                                                                                                                                                                                     SubConvId
                                                                                                                                                                                                                   :> ("groupinfo"
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[MLS]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "The group information"
                                                                                                                                                                                                                                GroupInfoData]
                                                                                                                                                                                                                            GroupInfoData))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-one-to-one-conversation@v2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "api-version"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-created"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V3
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NonBindingTeam
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     200
                                                                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     201
                                                                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-one-to-one-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-created"
                                                                                                                                                                                           :> (From
                                                                                                                                                                                                 'V3
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                       200
                                                                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                       201
                                                                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V5
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[VersionedRespond
                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                                          Conversation]
                                                                                                                                                                                                                                      Conversation))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V6
                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                             'V7
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                                               MLSPublicKey)]
                                                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                                                           MLSPublicKey))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V7
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> (QueryParam
                                                                                                                                                                                                                                           "format"
                                                                                                                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                                     SomeKey)]
                                                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                                                 SomeKey))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 Invite
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "add-members-to-conversation"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V5
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "code-check"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationCode
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Valid"]
                                                                                                                                                                                                                                                                              ()))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V4
                                                                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                               'V4
                                                                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                                                                                                                          Event]
                                                                                                                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "get-code"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation@v2" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> Sem r Conversation
getConversation))
    API
  (Named
     "get-conversation@v2"
     (Summary "Get a conversation by ID"
      :> (Until 'V3
          :> (MakesFederatedCall 'Galley "get-conversations"
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'ConvAccessDenied
                      :> (ZLocalUser
                          :> ("conversations"
                              :> (QualifiedCapture "cnv" ConvId
                                  :> MultiVerb
                                       'GET
                                       '[JSON]
                                       '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                       Conversation)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation@v5"
        (Summary "Get a conversation by ID"
         :> (From 'V3
             :> (Until 'V6
                 :> (MakesFederatedCall 'Galley "get-conversations"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[VersionedRespond
                                                  'V5 200 "Conversation" Conversation]
                                              Conversation)))))))))
      :<|> (Named
              "get-conversation"
              (Summary "Get a conversation by ID"
               :> (From 'V6
                   :> (MakesFederatedCall 'Galley "get-conversations"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (QualifiedCapture "cnv" ConvId
                                           :> Get '[JSON] Conversation))))))))
            :<|> (Named
                    "get-conversation-roles"
                    (Summary "Get existing roles available for the given conversation"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
                  :<|> (Named
                          "get-group-info"
                          (Summary "Get MLS group information"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "query-group-info"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'MLSMissingGroupInfo
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("groupinfo"
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[MLS]
                                                                    '[Respond
                                                                        200
                                                                        "The group information"
                                                                        GroupInfoData]
                                                                    GroupInfoData))))))))))
                        :<|> (Named
                                "list-conversation-ids-unqualified"
                                (Summary "[deprecated] Get all local conversation IDs."
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("ids"
                                                 :> (QueryParam'
                                                       '[Optional, Strict,
                                                         Description
                                                           "Conversation ID to start from (exclusive)"]
                                                       "start"
                                                       ConvId
                                                     :> (QueryParam'
                                                           '[Optional, Strict,
                                                             Description
                                                               "Maximum number of IDs to return"]
                                                           "size"
                                                           (Range 1 1000 Int32)
                                                         :> Get
                                                              '[JSON]
                                                              (ConversationList ConvId))))))))
                              :<|> (Named
                                      "list-conversation-ids-v2"
                                      (Summary "Get all conversation IDs."
                                       :> (Until 'V3
                                           :> (Description PaginationDocs
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list-ids"
                                                           :> (ReqBody
                                                                 '[JSON] GetPaginatedConversationIds
                                                               :> Post '[JSON] ConvIdsPage)))))))
                                    :<|> (Named
                                            "list-conversation-ids"
                                            (Summary "Get all conversation IDs."
                                             :> (From 'V3
                                                 :> (Description PaginationDocs
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list-ids"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       GetPaginatedConversationIds
                                                                     :> Post
                                                                          '[JSON] ConvIdsPage)))))))
                                          :<|> (Named
                                                  "get-conversations"
                                                  (Summary "Get all *local* conversations."
                                                   :> (Until 'V3
                                                       :> (Description
                                                             "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QueryParam'
                                                                         '[Optional, Strict,
                                                                           Description
                                                                             "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                         "ids"
                                                                         (Range
                                                                            1
                                                                            32
                                                                            (CommaSeparatedList
                                                                               ConvId))
                                                                       :> (QueryParam'
                                                                             '[Optional, Strict,
                                                                               Description
                                                                                 "Conversation ID to start from (exclusive)"]
                                                                             "start"
                                                                             ConvId
                                                                           :> (QueryParam'
                                                                                 '[Optional, Strict,
                                                                                   Description
                                                                                     "Maximum number of conversations to return"]
                                                                                 "size"
                                                                                 (Range 1 500 Int32)
                                                                               :> MultiVerb
                                                                                    'GET
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V2
                                                                                        200
                                                                                        "List of local conversations"
                                                                                        (ConversationList
                                                                                           Conversation)]
                                                                                    (ConversationList
                                                                                       Conversation)))))))))
                                                :<|> (Named
                                                        "list-conversations@v1"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (Until 'V2
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list"
                                                                             :> ("v2"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> Post
                                                                                          '[JSON]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations@v2"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V2
                                                                       :> (Until 'V3
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("list"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V2
                                                                                                    200
                                                                                                    "Conversation page"
                                                                                                    ConversationsResponse]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v5"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V3
                                                                             :> (Until 'V6
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("list"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[VersionedRespond
                                                                                                          'V5
                                                                                                          200
                                                                                                          "Conversation page"
                                                                                                          ConversationsResponse]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("list"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ListConversations
                                                                                                   :> Post
                                                                                                        '[JSON]
                                                                                                        ConversationsResponse)))))))
                                                                        :<|> (Named
                                                                                "get-conversation-by-reusable-code"
                                                                                (Summary
                                                                                   "Get limited conversation information by key/code pair"
                                                                                 :> (CanThrow
                                                                                       'CodeNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidConversationPassword
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (ZLocalUser
                                                                                                             :> ("conversations"
                                                                                                                 :> ("join"
                                                                                                                     :> (QueryParam'
                                                                                                                           '[Required,
                                                                                                                             Strict]
                                                                                                                           "key"
                                                                                                                           Key
                                                                                                                         :> (QueryParam'
                                                                                                                               '[Required,
                                                                                                                                 Strict]
                                                                                                                               "code"
                                                                                                                               Value
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  ConversationCoverView))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (DescriptionOAuthScope
                                                                                             'WriteConversations
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "api-version"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (Until
                                                                                                             'V3
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                           :> (Description
                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZOptConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                 'V2
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 NewConv
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           200
                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                           Conversation),
                                                                                                                                                                      WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           201
                                                                                                                                                                           "Conversation created"
                                                                                                                                                                           Conversation)]
                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v3"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (DescriptionOAuthScope
                                                                                                   'WriteConversations
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "api-version"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V3
                                                                                                                 :> (Until
                                                                                                                       'V4
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNonEmptyMemberList
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                     :> (Description
                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           NewConv
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V3
                                                                                                                                                                                     200
                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                     Conversation),
                                                                                                                                                                                WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V3
                                                                                                                                                                                     201
                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                     Conversation)]
                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                 Conversation)))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-not-fully-connected-backends"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V4
                                                                                                                       :> (Until
                                                                                                                             'V6
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             NonFederatingBackends
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 UnreachableBackends
                                                                                                                                                               :> (Description
                                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     NewConv
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V5
                                                                                                                                                                                               200
                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                               Conversation),
                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            CreateGroupConversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V5
                                                                                                                                                                                               201
                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                               CreateGroupConversation)]
                                                                                                                                                                                        CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-not-fully-connected-backends"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V6
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNonEmptyMemberList
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotConnected
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       NewConv
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V6
                                                                                                                                                                                                 200
                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              CreateGroupConversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V6
                                                                                                                                                                                                 201
                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                                                                          CreateGroupConversationResponse))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation@v2"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("self"
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V2
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V2
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V3
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("self"
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     Conversation)]
                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                 Conversation)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("self"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-mls-self-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Get the user's MLS self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("mls-self"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                  'V5
                                                                                                                                                                  200
                                                                                                                                                                  "The MLS self-conversation"
                                                                                                                                                                  Conversation]
                                                                                                                                                              Conversation)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-mls-self-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get the user's MLS self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("mls-self"
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "The MLS self-conversation"
                                                                                                                                                                    Conversation]
                                                                                                                                                                Conversation))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get information about an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "get-sub-conversation"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSSubConvUnsupportedConvType
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "subconv"
                                                                                                                                                                                       SubConvId
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'GET
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[Respond
                                                                                                                                                                                              200
                                                                                                                                                                                              "Subconversation"
                                                                                                                                                                                              PublicSubConversation]
                                                                                                                                                                                          PublicSubConversation)))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "leave-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Leave an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "leave-sub-conversation"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSProtocolErrorTag
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSStaleMessage
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZClient
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "subconv"
                                                                                                                                                                                                             SubConvId
                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "OK"]
                                                                                                                                                                                                                    ()))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "delete-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Delete an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "delete-sub-conversation"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSStaleMessage
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "subconv"
                                                                                                                                                                                                       SubConvId
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           DeleteSubConversationRequest
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Deletion successful"
                                                                                                                                                                                                                  ()]
                                                                                                                                                                                                              ())))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-subconversation-group-info"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get MLS group information of subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "query-group-info"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSMissingGroupInfo
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                       :> ("groupinfo"
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[MLS]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "The group information"
                                                                                                                                                                                                                    GroupInfoData]
                                                                                                                                                                                                                GroupInfoData))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-one-to-one-conversation@v2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create a 1:1 conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "api-version"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-created"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V3
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NonBindingTeam
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               NewConv
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         200
                                                                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         201
                                                                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                                                                     Conversation))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-one-to-one-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create a 1:1 conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-created"
                                                                                                                                                                               :> (From
                                                                                                                                                                                     'V3
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NonBindingTeam
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 NewConv
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                           200
                                                                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                           201
                                                                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                                                                       Conversation)))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V5
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V6
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                                              Conversation]
                                                                                                                                                                                                                          Conversation))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V6
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V7
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                                   MLSPublicKey)]
                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                               MLSPublicKey))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V7
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> (QueryParam
                                                                                                                                                                                                                               "format"
                                                                                                                                                                                                                               MLSPublicKeyFormat
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                                         SomeKey)]
                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                     SomeKey))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     Invite
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V5
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "code-check"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> ("code-check"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationCode
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Valid"]
                                                                                                                                                                                                                                                                  ()))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V4
                                                                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                   'V4
                                                                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Delete conversation code"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                                                                                                                              Event]
                                                                                                                                                                                                                                                                                          Event))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-code"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation@v2"
        (Summary "Get a conversation by ID"
         :> (Until 'V3
             :> (MakesFederatedCall 'Galley "get-conversations"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond 'V2 200 "Conversation" Conversation]
                                          Conversation))))))))
      :<|> (Named
              "get-conversation@v5"
              (Summary "Get a conversation by ID"
               :> (From 'V3
                   :> (Until 'V6
                       :> (MakesFederatedCall 'Galley "get-conversations"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[VersionedRespond
                                                        'V5 200 "Conversation" Conversation]
                                                    Conversation)))))))))
            :<|> (Named
                    "get-conversation"
                    (Summary "Get a conversation by ID"
                     :> (From 'V6
                         :> (MakesFederatedCall 'Galley "get-conversations"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> (QualifiedCapture "cnv" ConvId
                                                 :> Get '[JSON] Conversation))))))))
                  :<|> (Named
                          "get-conversation-roles"
                          (Summary "Get existing roles available for the given conversation"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (Capture "cnv" ConvId
                                               :> ("roles"
                                                   :> Get '[JSON] ConversationRolesList)))))))
                        :<|> (Named
                                "get-group-info"
                                (Summary "Get MLS group information"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "query-group-info"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'MLSMissingGroupInfo
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("groupinfo"
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[MLS]
                                                                          '[Respond
                                                                              200
                                                                              "The group information"
                                                                              GroupInfoData]
                                                                          GroupInfoData))))))))))
                              :<|> (Named
                                      "list-conversation-ids-unqualified"
                                      (Summary "[deprecated] Get all local conversation IDs."
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("ids"
                                                       :> (QueryParam'
                                                             '[Optional, Strict,
                                                               Description
                                                                 "Conversation ID to start from (exclusive)"]
                                                             "start"
                                                             ConvId
                                                           :> (QueryParam'
                                                                 '[Optional, Strict,
                                                                   Description
                                                                     "Maximum number of IDs to return"]
                                                                 "size"
                                                                 (Range 1 1000 Int32)
                                                               :> Get
                                                                    '[JSON]
                                                                    (ConversationList ConvId))))))))
                                    :<|> (Named
                                            "list-conversation-ids-v2"
                                            (Summary "Get all conversation IDs."
                                             :> (Until 'V3
                                                 :> (Description PaginationDocs
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list-ids"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       GetPaginatedConversationIds
                                                                     :> Post
                                                                          '[JSON] ConvIdsPage)))))))
                                          :<|> (Named
                                                  "list-conversation-ids"
                                                  (Summary "Get all conversation IDs."
                                                   :> (From 'V3
                                                       :> (Description PaginationDocs
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list-ids"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             GetPaginatedConversationIds
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConvIdsPage)))))))
                                                :<|> (Named
                                                        "get-conversations"
                                                        (Summary "Get all *local* conversations."
                                                         :> (Until 'V3
                                                             :> (Description
                                                                   "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QueryParam'
                                                                               '[Optional, Strict,
                                                                                 Description
                                                                                   "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                               "ids"
                                                                               (Range
                                                                                  1
                                                                                  32
                                                                                  (CommaSeparatedList
                                                                                     ConvId))
                                                                             :> (QueryParam'
                                                                                   '[Optional,
                                                                                     Strict,
                                                                                     Description
                                                                                       "Conversation ID to start from (exclusive)"]
                                                                                   "start"
                                                                                   ConvId
                                                                                 :> (QueryParam'
                                                                                       '[Optional,
                                                                                         Strict,
                                                                                         Description
                                                                                           "Maximum number of conversations to return"]
                                                                                       "size"
                                                                                       (Range
                                                                                          1
                                                                                          500
                                                                                          Int32)
                                                                                     :> MultiVerb
                                                                                          'GET
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V2
                                                                                              200
                                                                                              "List of local conversations"
                                                                                              (ConversationList
                                                                                                 Conversation)]
                                                                                          (ConversationList
                                                                                             Conversation)))))))))
                                                      :<|> (Named
                                                              "list-conversations@v1"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (Until 'V2
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("list"
                                                                                   :> ("v2"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> Post
                                                                                                '[JSON]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v2"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V2
                                                                             :> (Until 'V3
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("list"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[VersionedRespond
                                                                                                          'V2
                                                                                                          200
                                                                                                          "Conversation page"
                                                                                                          ConversationsResponse]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations@v5"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V3
                                                                                   :> (Until 'V6
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("list"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ListConversations
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[VersionedRespond
                                                                                                                'V5
                                                                                                                200
                                                                                                                "Conversation page"
                                                                                                                ConversationsResponse]
                                                                                                            ConversationsResponse))))))))
                                                                        :<|> (Named
                                                                                "list-conversations"
                                                                                (Summary
                                                                                   "Get conversation metadata for a list of conversation ids"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "get-conversations"
                                                                                     :> (From 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("list"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ListConversations
                                                                                                         :> Post
                                                                                                              '[JSON]
                                                                                                              ConversationsResponse)))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-by-reusable-code"
                                                                                      (Summary
                                                                                         "Get limited conversation information by key/code pair"
                                                                                       :> (CanThrow
                                                                                             'CodeNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidConversationPassword
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (ZLocalUser
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("join"
                                                                                                                           :> (QueryParam'
                                                                                                                                 '[Required,
                                                                                                                                   Strict]
                                                                                                                                 "key"
                                                                                                                                 Key
                                                                                                                               :> (QueryParam'
                                                                                                                                     '[Required,
                                                                                                                                       Strict]
                                                                                                                                     "code"
                                                                                                                                     Value
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        ConversationCoverView))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (DescriptionOAuthScope
                                                                                                   'WriteConversations
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "api-version"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (Until
                                                                                                                   'V3
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                 :> (Description
                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZOptConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                       'V2
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       NewConv
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 200
                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                 Conversation),
                                                                                                                                                                            WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 201
                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                 Conversation)]
                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v3"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (DescriptionOAuthScope
                                                                                                         'WriteConversations
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "api-version"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V3
                                                                                                                       :> (Until
                                                                                                                             'V4
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                           :> (Description
                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 NewConv
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V3
                                                                                                                                                                                           200
                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                           Conversation),
                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V3
                                                                                                                                                                                           201
                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                       Conversation)))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-not-fully-connected-backends"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V4
                                                                                                                             :> (Until
                                                                                                                                   'V6
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           NewConv
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V5
                                                                                                                                                                                                     200
                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  CreateGroupConversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V5
                                                                                                                                                                                                     201
                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-group-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a new conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-not-fully-connected-backends"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-created"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (From
                                                                                                                                     'V6
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNonEmptyMemberList
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotConnected
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (Description
                                                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             NewConv
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                       200
                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                    CreateGroupConversation
                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                       'V6
                                                                                                                                                                                                       201
                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                                                                CreateGroupConversationResponse))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation@v2"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("self"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V2
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V2
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V3
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("self"
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           Conversation)]
                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                       Conversation)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-self-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Create a self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("self"
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             Conversation)]
                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                         Conversation))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-mls-self-conversation@v5"
                                                                                                                                      (Summary
                                                                                                                                         "Get the user's MLS self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (Until
                                                                                                                                                 'V6
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("mls-self"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                        'V5
                                                                                                                                                                        200
                                                                                                                                                                        "The MLS self-conversation"
                                                                                                                                                                        Conversation]
                                                                                                                                                                    Conversation)))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-mls-self-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get the user's MLS self-conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V6
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("mls-self"
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "The MLS self-conversation"
                                                                                                                                                                          Conversation]
                                                                                                                                                                      Conversation))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get information about an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "get-sub-conversation"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSSubConvUnsupportedConvType
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "subconv"
                                                                                                                                                                                             SubConvId
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'GET
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Subconversation"
                                                                                                                                                                                                    PublicSubConversation]
                                                                                                                                                                                                PublicSubConversation)))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "leave-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Leave an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "leave-sub-conversation"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSProtocolErrorTag
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSStaleMessage
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZClient
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "OK"]
                                                                                                                                                                                                                          ()))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "delete-subconversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Delete an MLS subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "delete-sub-conversation"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSStaleMessage
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "subconv"
                                                                                                                                                                                                             SubConvId
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 DeleteSubConversationRequest
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Deletion successful"
                                                                                                                                                                                                                        ()]
                                                                                                                                                                                                                    ())))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-subconversation-group-info"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get MLS group information of subconversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "query-group-info"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSMissingGroupInfo
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                               "subconv"
                                                                                                                                                                                                               SubConvId
                                                                                                                                                                                                             :> ("groupinfo"
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[MLS]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "The group information"
                                                                                                                                                                                                                          GroupInfoData]
                                                                                                                                                                                                                      GroupInfoData))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-one-to-one-conversation@v2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create a 1:1 conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "api-version"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-created"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V3
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NonBindingTeam
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               200
                                                                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               201
                                                                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                                                                           Conversation))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-one-to-one-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-created"
                                                                                                                                                                                     :> (From
                                                                                                                                                                                           'V3
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NonBindingTeam
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                 200
                                                                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                 201
                                                                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                                                                             Conversation)))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V5
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V6
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[VersionedRespond
                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                                    Conversation]
                                                                                                                                                                                                                                Conversation))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V6
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V7
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                                         MLSPublicKey)]
                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                     MLSPublicKey))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V7
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> (QueryParam
                                                                                                                                                                                                                                     "format"
                                                                                                                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                                               SomeKey)]
                                                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                                                           SomeKey))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           Invite
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "add-members-to-conversation"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V5
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "code-check"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> ("code-check"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationCode
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Valid"]
                                                                                                                                                                                                                                                                        ()))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V4
                                                                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                         'V4
                                                                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                                                                                                                    Event]
                                                                                                                                                                                                                                                                                                Event))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "get-code"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation@v5" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> Sem r Conversation
getConversation))
    API
  (Named
     "get-conversation@v5"
     (Summary "Get a conversation by ID"
      :> (From 'V3
          :> (Until 'V6
              :> (MakesFederatedCall 'Galley "get-conversations"
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'ConvAccessDenied
                          :> (ZLocalUser
                              :> ("conversations"
                                  :> (QualifiedCapture "cnv" ConvId
                                      :> MultiVerb
                                           'GET
                                           '[JSON]
                                           '[VersionedRespond 'V5 200 "Conversation" Conversation]
                                           Conversation))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation"
        (Summary "Get a conversation by ID"
         :> (From 'V6
             :> (MakesFederatedCall 'Galley "get-conversations"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> Get '[JSON] Conversation))))))))
      :<|> (Named
              "get-conversation-roles"
              (Summary "Get existing roles available for the given conversation"
               :> (CanThrow 'ConvNotFound
                   :> (CanThrow 'ConvAccessDenied
                       :> (ZLocalUser
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
            :<|> (Named
                    "get-group-info"
                    (Summary "Get MLS group information"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "query-group-info"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'MLSMissingGroupInfo
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("groupinfo"
                                                         :> MultiVerb
                                                              'GET
                                                              '[MLS]
                                                              '[Respond
                                                                  200
                                                                  "The group information"
                                                                  GroupInfoData]
                                                              GroupInfoData))))))))))
                  :<|> (Named
                          "list-conversation-ids-unqualified"
                          (Summary "[deprecated] Get all local conversation IDs."
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("ids"
                                           :> (QueryParam'
                                                 '[Optional, Strict,
                                                   Description
                                                     "Conversation ID to start from (exclusive)"]
                                                 "start"
                                                 ConvId
                                               :> (QueryParam'
                                                     '[Optional, Strict,
                                                       Description
                                                         "Maximum number of IDs to return"]
                                                     "size"
                                                     (Range 1 1000 Int32)
                                                   :> Get '[JSON] (ConversationList ConvId))))))))
                        :<|> (Named
                                "list-conversation-ids-v2"
                                (Summary "Get all conversation IDs."
                                 :> (Until 'V3
                                     :> (Description PaginationDocs
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list-ids"
                                                     :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                         :> Post '[JSON] ConvIdsPage)))))))
                              :<|> (Named
                                      "list-conversation-ids"
                                      (Summary "Get all conversation IDs."
                                       :> (From 'V3
                                           :> (Description PaginationDocs
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list-ids"
                                                           :> (ReqBody
                                                                 '[JSON] GetPaginatedConversationIds
                                                               :> Post '[JSON] ConvIdsPage)))))))
                                    :<|> (Named
                                            "get-conversations"
                                            (Summary "Get all *local* conversations."
                                             :> (Until 'V3
                                                 :> (Description
                                                       "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QueryParam'
                                                                   '[Optional, Strict,
                                                                     Description
                                                                       "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                   "ids"
                                                                   (Range
                                                                      1
                                                                      32
                                                                      (CommaSeparatedList ConvId))
                                                                 :> (QueryParam'
                                                                       '[Optional, Strict,
                                                                         Description
                                                                           "Conversation ID to start from (exclusive)"]
                                                                       "start"
                                                                       ConvId
                                                                     :> (QueryParam'
                                                                           '[Optional, Strict,
                                                                             Description
                                                                               "Maximum number of conversations to return"]
                                                                           "size"
                                                                           (Range 1 500 Int32)
                                                                         :> MultiVerb
                                                                              'GET
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V2
                                                                                  200
                                                                                  "List of local conversations"
                                                                                  (ConversationList
                                                                                     Conversation)]
                                                                              (ConversationList
                                                                                 Conversation)))))))))
                                          :<|> (Named
                                                  "list-conversations@v1"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (Until 'V2
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list"
                                                                       :> ("v2"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> Post
                                                                                    '[JSON]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations@v2"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V2
                                                                 :> (Until 'V3
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("list"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V2
                                                                                              200
                                                                                              "Conversation page"
                                                                                              ConversationsResponse]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations@v5"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V3
                                                                       :> (Until 'V6
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("list"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V5
                                                                                                    200
                                                                                                    "Conversation page"
                                                                                                    ConversationsResponse]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("list"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ListConversations
                                                                                             :> Post
                                                                                                  '[JSON]
                                                                                                  ConversationsResponse)))))))
                                                                  :<|> (Named
                                                                          "get-conversation-by-reusable-code"
                                                                          (Summary
                                                                             "Get limited conversation information by key/code pair"
                                                                           :> (CanThrow
                                                                                 'CodeNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidConversationPassword
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (ZLocalUser
                                                                                                       :> ("conversations"
                                                                                                           :> ("join"
                                                                                                               :> (QueryParam'
                                                                                                                     '[Required,
                                                                                                                       Strict]
                                                                                                                     "key"
                                                                                                                     Key
                                                                                                                   :> (QueryParam'
                                                                                                                         '[Required,
                                                                                                                           Strict]
                                                                                                                         "code"
                                                                                                                         Value
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            ConversationCoverView))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v2"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (DescriptionOAuthScope
                                                                                       'WriteConversations
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "api-version"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (Until
                                                                                                       'V3
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'MLSNonEmptyMemberList
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                     :> (Description
                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZOptConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                           'V2
                                                                                                                                                           '[JSON]
                                                                                                                                                           NewConv
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     200
                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                     Conversation),
                                                                                                                                                                WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     201
                                                                                                                                                                     "Conversation created"
                                                                                                                                                                     Conversation)]
                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v3"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (DescriptionOAuthScope
                                                                                             'WriteConversations
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "api-version"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V3
                                                                                                           :> (Until
                                                                                                                 'V4
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNonEmptyMemberList
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                               :> (Description
                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZOptConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     NewConv
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V3
                                                                                                                                                                               200
                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                               Conversation),
                                                                                                                                                                          WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V3
                                                                                                                                                                               201
                                                                                                                                                                               "Conversation created"
                                                                                                                                                                               Conversation)]
                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                           Conversation)))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v5"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-not-fully-connected-backends"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V4
                                                                                                                 :> (Until
                                                                                                                       'V6
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNonEmptyMemberList
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       NonFederatingBackends
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           UnreachableBackends
                                                                                                                                                         :> (Description
                                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               NewConv
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V5
                                                                                                                                                                                         200
                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                         Conversation),
                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      CreateGroupConversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V5
                                                                                                                                                                                         201
                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                         CreateGroupConversation)]
                                                                                                                                                                                  CreateGroupConversationResponse)))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-not-fully-connected-backends"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V6
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (Description
                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 NewConv
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V6
                                                                                                                                                                                           200
                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                           Conversation),
                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        CreateGroupConversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V6
                                                                                                                                                                                           201
                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                                                    CreateGroupConversationResponse))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation@v2"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("self"
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V2
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V2
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (From
                                                                                                                     'V3
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("self"
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               Conversation)]
                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                           Conversation)))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("self"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-mls-self-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Get the user's MLS self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("mls-self"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[VersionedRespond
                                                                                                                                                            'V5
                                                                                                                                                            200
                                                                                                                                                            "The MLS self-conversation"
                                                                                                                                                            Conversation]
                                                                                                                                                        Conversation)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-mls-self-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Get the user's MLS self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("mls-self"
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "The MLS self-conversation"
                                                                                                                                                              Conversation]
                                                                                                                                                          Conversation))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get information about an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "get-sub-conversation"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSSubConvUnsupportedConvType
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "subconv"
                                                                                                                                                                                 SubConvId
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'GET
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[Respond
                                                                                                                                                                                        200
                                                                                                                                                                                        "Subconversation"
                                                                                                                                                                                        PublicSubConversation]
                                                                                                                                                                                    PublicSubConversation)))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "leave-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Leave an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "leave-sub-conversation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSProtocolErrorTag
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSStaleMessage
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZClient
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "subconv"
                                                                                                                                                                                                       SubConvId
                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "OK"]
                                                                                                                                                                                                              ()))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "delete-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Delete an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "delete-sub-conversation"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSStaleMessage
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "subconv"
                                                                                                                                                                                                 SubConvId
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     DeleteSubConversationRequest
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Deletion successful"
                                                                                                                                                                                                            ()]
                                                                                                                                                                                                        ())))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-subconversation-group-info"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get MLS group information of subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "query-group-info"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSMissingGroupInfo
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                 :> ("groupinfo"
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[MLS]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "The group information"
                                                                                                                                                                                                              GroupInfoData]
                                                                                                                                                                                                          GroupInfoData))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-one-to-one-conversation@v2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create a 1:1 conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "api-version"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-created"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V3
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NonBindingTeam
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         NewConv
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   200
                                                                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   201
                                                                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                                                                               Conversation))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-one-to-one-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create a 1:1 conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-created"
                                                                                                                                                                         :> (From
                                                                                                                                                                               'V3
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NonBindingTeam
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                     200
                                                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                     201
                                                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                                                 Conversation)))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V6
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                                        Conversation]
                                                                                                                                                                                                                    Conversation))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V6
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V7
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                                             MLSPublicKey)]
                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                         MLSPublicKey))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V7
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> (QueryParam
                                                                                                                                                                                                                         "format"
                                                                                                                                                                                                                         MLSPublicKeyFormat
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                                   SomeKey)]
                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                               SomeKey))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               Invite
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V5
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "code-check"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Check validity of a conversation code."
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> ("code-check"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationCode
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Valid"]
                                                                                                                                                                                                                                                            ()))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V4
                                                                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                             'V4
                                                                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Delete conversation code"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                                                                                                                        Event]
                                                                                                                                                                                                                                                                                    Event))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-code"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "remove-member"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation@v5"
        (Summary "Get a conversation by ID"
         :> (From 'V3
             :> (Until 'V6
                 :> (MakesFederatedCall 'Galley "get-conversations"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[VersionedRespond
                                                  'V5 200 "Conversation" Conversation]
                                              Conversation)))))))))
      :<|> (Named
              "get-conversation"
              (Summary "Get a conversation by ID"
               :> (From 'V6
                   :> (MakesFederatedCall 'Galley "get-conversations"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (QualifiedCapture "cnv" ConvId
                                           :> Get '[JSON] Conversation))))))))
            :<|> (Named
                    "get-conversation-roles"
                    (Summary "Get existing roles available for the given conversation"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (Capture "cnv" ConvId
                                         :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
                  :<|> (Named
                          "get-group-info"
                          (Summary "Get MLS group information"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "query-group-info"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'MLSMissingGroupInfo
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("groupinfo"
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[MLS]
                                                                    '[Respond
                                                                        200
                                                                        "The group information"
                                                                        GroupInfoData]
                                                                    GroupInfoData))))))))))
                        :<|> (Named
                                "list-conversation-ids-unqualified"
                                (Summary "[deprecated] Get all local conversation IDs."
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("ids"
                                                 :> (QueryParam'
                                                       '[Optional, Strict,
                                                         Description
                                                           "Conversation ID to start from (exclusive)"]
                                                       "start"
                                                       ConvId
                                                     :> (QueryParam'
                                                           '[Optional, Strict,
                                                             Description
                                                               "Maximum number of IDs to return"]
                                                           "size"
                                                           (Range 1 1000 Int32)
                                                         :> Get
                                                              '[JSON]
                                                              (ConversationList ConvId))))))))
                              :<|> (Named
                                      "list-conversation-ids-v2"
                                      (Summary "Get all conversation IDs."
                                       :> (Until 'V3
                                           :> (Description PaginationDocs
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list-ids"
                                                           :> (ReqBody
                                                                 '[JSON] GetPaginatedConversationIds
                                                               :> Post '[JSON] ConvIdsPage)))))))
                                    :<|> (Named
                                            "list-conversation-ids"
                                            (Summary "Get all conversation IDs."
                                             :> (From 'V3
                                                 :> (Description PaginationDocs
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list-ids"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       GetPaginatedConversationIds
                                                                     :> Post
                                                                          '[JSON] ConvIdsPage)))))))
                                          :<|> (Named
                                                  "get-conversations"
                                                  (Summary "Get all *local* conversations."
                                                   :> (Until 'V3
                                                       :> (Description
                                                             "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QueryParam'
                                                                         '[Optional, Strict,
                                                                           Description
                                                                             "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                         "ids"
                                                                         (Range
                                                                            1
                                                                            32
                                                                            (CommaSeparatedList
                                                                               ConvId))
                                                                       :> (QueryParam'
                                                                             '[Optional, Strict,
                                                                               Description
                                                                                 "Conversation ID to start from (exclusive)"]
                                                                             "start"
                                                                             ConvId
                                                                           :> (QueryParam'
                                                                                 '[Optional, Strict,
                                                                                   Description
                                                                                     "Maximum number of conversations to return"]
                                                                                 "size"
                                                                                 (Range 1 500 Int32)
                                                                               :> MultiVerb
                                                                                    'GET
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V2
                                                                                        200
                                                                                        "List of local conversations"
                                                                                        (ConversationList
                                                                                           Conversation)]
                                                                                    (ConversationList
                                                                                       Conversation)))))))))
                                                :<|> (Named
                                                        "list-conversations@v1"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (Until 'V2
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list"
                                                                             :> ("v2"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> Post
                                                                                          '[JSON]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations@v2"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V2
                                                                       :> (Until 'V3
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("list"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V2
                                                                                                    200
                                                                                                    "Conversation page"
                                                                                                    ConversationsResponse]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations@v5"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V3
                                                                             :> (Until 'V6
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("list"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ListConversations
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[VersionedRespond
                                                                                                          'V5
                                                                                                          200
                                                                                                          "Conversation page"
                                                                                                          ConversationsResponse]
                                                                                                      ConversationsResponse))))))))
                                                                  :<|> (Named
                                                                          "list-conversations"
                                                                          (Summary
                                                                             "Get conversation metadata for a list of conversation ids"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "get-conversations"
                                                                               :> (From 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("list"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ListConversations
                                                                                                   :> Post
                                                                                                        '[JSON]
                                                                                                        ConversationsResponse)))))))
                                                                        :<|> (Named
                                                                                "get-conversation-by-reusable-code"
                                                                                (Summary
                                                                                   "Get limited conversation information by key/code pair"
                                                                                 :> (CanThrow
                                                                                       'CodeNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidConversationPassword
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (ZLocalUser
                                                                                                             :> ("conversations"
                                                                                                                 :> ("join"
                                                                                                                     :> (QueryParam'
                                                                                                                           '[Required,
                                                                                                                             Strict]
                                                                                                                           "key"
                                                                                                                           Key
                                                                                                                         :> (QueryParam'
                                                                                                                               '[Required,
                                                                                                                                 Strict]
                                                                                                                               "code"
                                                                                                                               Value
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  ConversationCoverView))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (DescriptionOAuthScope
                                                                                             'WriteConversations
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "api-version"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (Until
                                                                                                             'V3
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                           :> (Description
                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZOptConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                 'V2
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 NewConv
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           200
                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                           Conversation),
                                                                                                                                                                      WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           201
                                                                                                                                                                           "Conversation created"
                                                                                                                                                                           Conversation)]
                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v3"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (DescriptionOAuthScope
                                                                                                   'WriteConversations
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "api-version"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V3
                                                                                                                 :> (Until
                                                                                                                       'V4
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNonEmptyMemberList
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                     :> (Description
                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           NewConv
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V3
                                                                                                                                                                                     200
                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                     Conversation),
                                                                                                                                                                                WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V3
                                                                                                                                                                                     201
                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                     Conversation)]
                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                 Conversation)))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-not-fully-connected-backends"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V4
                                                                                                                       :> (Until
                                                                                                                             'V6
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             NonFederatingBackends
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 UnreachableBackends
                                                                                                                                                               :> (Description
                                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     NewConv
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V5
                                                                                                                                                                                               200
                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                               Conversation),
                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            CreateGroupConversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V5
                                                                                                                                                                                               201
                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                               CreateGroupConversation)]
                                                                                                                                                                                        CreateGroupConversationResponse)))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-group-conversation"
                                                                                                        (Summary
                                                                                                           "Create a new conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-not-fully-connected-backends"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-created"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (From
                                                                                                                               'V6
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNonEmptyMemberList
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotConnected
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       NewConv
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              Conversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V6
                                                                                                                                                                                                 200
                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                              CreateGroupConversation
                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                 'V6
                                                                                                                                                                                                 201
                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                                                                          CreateGroupConversationResponse))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation@v2"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("self"
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V2
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V2
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V3
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("self"
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     Conversation)]
                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                 Conversation)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-self-conversation"
                                                                                                                          (Summary
                                                                                                                             "Create a self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("self"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-mls-self-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Get the user's MLS self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("mls-self"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                  'V5
                                                                                                                                                                  200
                                                                                                                                                                  "The MLS self-conversation"
                                                                                                                                                                  Conversation]
                                                                                                                                                              Conversation)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-mls-self-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get the user's MLS self-conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("mls-self"
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "The MLS self-conversation"
                                                                                                                                                                    Conversation]
                                                                                                                                                                Conversation))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get information about an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "get-sub-conversation"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSSubConvUnsupportedConvType
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "subconv"
                                                                                                                                                                                       SubConvId
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'GET
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[Respond
                                                                                                                                                                                              200
                                                                                                                                                                                              "Subconversation"
                                                                                                                                                                                              PublicSubConversation]
                                                                                                                                                                                          PublicSubConversation)))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "leave-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Leave an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "leave-sub-conversation"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSProtocolErrorTag
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSStaleMessage
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZClient
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "subconv"
                                                                                                                                                                                                             SubConvId
                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "OK"]
                                                                                                                                                                                                                    ()))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "delete-subconversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Delete an MLS subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "delete-sub-conversation"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSStaleMessage
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "subconv"
                                                                                                                                                                                                       SubConvId
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           DeleteSubConversationRequest
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Deletion successful"
                                                                                                                                                                                                                  ()]
                                                                                                                                                                                                              ())))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-subconversation-group-info"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get MLS group information of subconversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "query-group-info"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSMissingGroupInfo
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                         "subconv"
                                                                                                                                                                                                         SubConvId
                                                                                                                                                                                                       :> ("groupinfo"
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[MLS]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "The group information"
                                                                                                                                                                                                                    GroupInfoData]
                                                                                                                                                                                                                GroupInfoData))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-one-to-one-conversation@v2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create a 1:1 conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "api-version"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-created"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V3
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NonBindingTeam
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               NewConv
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         200
                                                                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         201
                                                                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                                                                     Conversation))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-one-to-one-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create a 1:1 conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-created"
                                                                                                                                                                               :> (From
                                                                                                                                                                                     'V3
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NonBindingTeam
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 NewConv
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                           200
                                                                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                           201
                                                                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                                                                       Conversation)))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V5
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V6
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                                              Conversation]
                                                                                                                                                                                                                          Conversation))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V6
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V7
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                                   MLSPublicKey)]
                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                               MLSPublicKey))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-one-to-one-mls-conversation"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V7
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> (QueryParam
                                                                                                                                                                                                                               "format"
                                                                                                                                                                                                                               MLSPublicKeyFormat
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                                         SomeKey)]
                                                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                                                     SomeKey))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     Invite
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "add-members-to-conversation"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V5
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "code-check"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> ("code-check"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationCode
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Valid"]
                                                                                                                                                                                                                                                                  ()))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V4
                                                                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                   'V4
                                                                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Delete conversation code"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                                                                                                                              Event]
                                                                                                                                                                                                                                                                                          Event))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-code"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      Conversation)
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> Sem r Conversation
getConversation))
    API
  (Named
     "get-conversation"
     (Summary "Get a conversation by ID"
      :> (From 'V6
          :> (MakesFederatedCall 'Galley "get-conversations"
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'ConvAccessDenied
                      :> (ZLocalUser
                          :> ("conversations"
                              :> (QualifiedCapture "cnv" ConvId
                                  :> Get '[JSON] Conversation)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation-roles"
        (Summary "Get existing roles available for the given conversation"
         :> (CanThrow 'ConvNotFound
             :> (CanThrow 'ConvAccessDenied
                 :> (ZLocalUser
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
      :<|> (Named
              "get-group-info"
              (Summary "Get MLS group information"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "query-group-info"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'MLSMissingGroupInfo
                               :> (CanThrow 'MLSNotEnabled
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("groupinfo"
                                                   :> MultiVerb
                                                        'GET
                                                        '[MLS]
                                                        '[Respond
                                                            200
                                                            "The group information"
                                                            GroupInfoData]
                                                        GroupInfoData))))))))))
            :<|> (Named
                    "list-conversation-ids-unqualified"
                    (Summary "[deprecated] Get all local conversation IDs."
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("ids"
                                     :> (QueryParam'
                                           '[Optional, Strict,
                                             Description
                                               "Conversation ID to start from (exclusive)"]
                                           "start"
                                           ConvId
                                         :> (QueryParam'
                                               '[Optional, Strict,
                                                 Description "Maximum number of IDs to return"]
                                               "size"
                                               (Range 1 1000 Int32)
                                             :> Get '[JSON] (ConversationList ConvId))))))))
                  :<|> (Named
                          "list-conversation-ids-v2"
                          (Summary "Get all conversation IDs."
                           :> (Until 'V3
                               :> (Description PaginationDocs
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list-ids"
                                               :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                   :> Post '[JSON] ConvIdsPage)))))))
                        :<|> (Named
                                "list-conversation-ids"
                                (Summary "Get all conversation IDs."
                                 :> (From 'V3
                                     :> (Description PaginationDocs
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list-ids"
                                                     :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                         :> Post '[JSON] ConvIdsPage)))))))
                              :<|> (Named
                                      "get-conversations"
                                      (Summary "Get all *local* conversations."
                                       :> (Until 'V3
                                           :> (Description
                                                 "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QueryParam'
                                                             '[Optional, Strict,
                                                               Description
                                                                 "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                             "ids"
                                                             (Range
                                                                1 32 (CommaSeparatedList ConvId))
                                                           :> (QueryParam'
                                                                 '[Optional, Strict,
                                                                   Description
                                                                     "Conversation ID to start from (exclusive)"]
                                                                 "start"
                                                                 ConvId
                                                               :> (QueryParam'
                                                                     '[Optional, Strict,
                                                                       Description
                                                                         "Maximum number of conversations to return"]
                                                                     "size"
                                                                     (Range 1 500 Int32)
                                                                   :> MultiVerb
                                                                        'GET
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V2
                                                                            200
                                                                            "List of local conversations"
                                                                            (ConversationList
                                                                               Conversation)]
                                                                        (ConversationList
                                                                           Conversation)))))))))
                                    :<|> (Named
                                            "list-conversations@v1"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (Until 'V2
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list"
                                                                 :> ("v2"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> Post
                                                                              '[JSON]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations@v2"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V2
                                                           :> (Until 'V3
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("list"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V2
                                                                                        200
                                                                                        "Conversation page"
                                                                                        ConversationsResponse]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations@v5"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V3
                                                                 :> (Until 'V6
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("list"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V5
                                                                                              200
                                                                                              "Conversation page"
                                                                                              ConversationsResponse]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("list"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ListConversations
                                                                                       :> Post
                                                                                            '[JSON]
                                                                                            ConversationsResponse)))))))
                                                            :<|> (Named
                                                                    "get-conversation-by-reusable-code"
                                                                    (Summary
                                                                       "Get limited conversation information by key/code pair"
                                                                     :> (CanThrow 'CodeNotFound
                                                                         :> (CanThrow
                                                                               'InvalidConversationPassword
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> ("join"
                                                                                                         :> (QueryParam'
                                                                                                               '[Required,
                                                                                                                 Strict]
                                                                                                               "key"
                                                                                                               Key
                                                                                                             :> (QueryParam'
                                                                                                                   '[Required,
                                                                                                                     Strict]
                                                                                                                   "code"
                                                                                                                   Value
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      ConversationCoverView))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v2"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (DescriptionOAuthScope
                                                                                 'WriteConversations
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "api-version"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (Until
                                                                                                 'V3
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'MLSNonEmptyMemberList
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                               :> (Description
                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZOptConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                     'V2
                                                                                                                                                     '[JSON]
                                                                                                                                                     NewConv
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               200
                                                                                                                                                               "Conversation existed"
                                                                                                                                                               Conversation),
                                                                                                                                                          WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               201
                                                                                                                                                               "Conversation created"
                                                                                                                                                               Conversation)]
                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                           Conversation))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v3"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (DescriptionOAuthScope
                                                                                       'WriteConversations
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "api-version"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V3
                                                                                                     :> (Until
                                                                                                           'V4
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                         :> (Description
                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZOptConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               NewConv
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V3
                                                                                                                                                                         200
                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                         Conversation),
                                                                                                                                                                    WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V3
                                                                                                                                                                         201
                                                                                                                                                                         "Conversation created"
                                                                                                                                                                         Conversation)]
                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                     Conversation)))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v5"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-not-fully-connected-backends"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V4
                                                                                                           :> (Until
                                                                                                                 'V6
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNonEmptyMemberList
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                           :> (CanThrow
                                                                                                                                                 NonFederatingBackends
                                                                                                                                               :> (CanThrow
                                                                                                                                                     UnreachableBackends
                                                                                                                                                   :> (Description
                                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         NewConv
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V5
                                                                                                                                                                                   200
                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                   Conversation),
                                                                                                                                                                              WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                CreateGroupConversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V5
                                                                                                                                                                                   201
                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                   CreateGroupConversation)]
                                                                                                                                                                            CreateGroupConversationResponse)))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-not-fully-connected-backends"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V6
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (Description
                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           NewConv
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V6
                                                                                                                                                                                     200
                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                     Conversation),
                                                                                                                                                                                WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  CreateGroupConversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V6
                                                                                                                                                                                     201
                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                                                              CreateGroupConversationResponse))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("self"
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V2
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V2
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (From
                                                                                                               'V3
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("self"
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         Conversation)]
                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                     Conversation)))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("self"
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-mls-self-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Get the user's MLS self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("mls-self"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[VersionedRespond
                                                                                                                                                      'V5
                                                                                                                                                      200
                                                                                                                                                      "The MLS self-conversation"
                                                                                                                                                      Conversation]
                                                                                                                                                  Conversation)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-mls-self-conversation"
                                                                                                                          (Summary
                                                                                                                             "Get the user's MLS self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("mls-self"
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "The MLS self-conversation"
                                                                                                                                                        Conversation]
                                                                                                                                                    Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Get information about an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "get-sub-conversation"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSSubConvUnsupportedConvType
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "subconv"
                                                                                                                                                                           SubConvId
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'GET
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[Respond
                                                                                                                                                                                  200
                                                                                                                                                                                  "Subconversation"
                                                                                                                                                                                  PublicSubConversation]
                                                                                                                                                                              PublicSubConversation)))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "leave-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Leave an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "leave-sub-conversation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSProtocolErrorTag
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSStaleMessage
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZClient
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "subconv"
                                                                                                                                                                                                 SubConvId
                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "OK"]
                                                                                                                                                                                                        ()))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "delete-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Delete an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "delete-sub-conversation"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSStaleMessage
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "subconv"
                                                                                                                                                                                           SubConvId
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               DeleteSubConversationRequest
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Deletion successful"
                                                                                                                                                                                                      ()]
                                                                                                                                                                                                  ())))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-subconversation-group-info"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get MLS group information of subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "query-group-info"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSMissingGroupInfo
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "subconv"
                                                                                                                                                                                             SubConvId
                                                                                                                                                                                           :> ("groupinfo"
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[MLS]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "The group information"
                                                                                                                                                                                                        GroupInfoData]
                                                                                                                                                                                                    GroupInfoData))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-one-to-one-conversation@v2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create a 1:1 conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "api-version"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-created"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V3
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NonBindingTeam
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             200
                                                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             201
                                                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                                                                         Conversation))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-one-to-one-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create a 1:1 conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-created"
                                                                                                                                                                   :> (From
                                                                                                                                                                         'V3
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NonBindingTeam
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                               200
                                                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                               201
                                                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                                                           Conversation)))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V6
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                           UserId
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'GET
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                                  Conversation]
                                                                                                                                                                                                              Conversation))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V6
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V7
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                             UserId
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                                       MLSPublicKey)]
                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                   MLSPublicKey))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V7
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> (QueryParam
                                                                                                                                                                                                                   "format"
                                                                                                                                                                                                                   MLSPublicKeyFormat
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                                             SomeKey)]
                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                         SomeKey))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         Invite
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation-unqualified2"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> ("v2"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V5
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Join a conversation using a reusable code"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "code-check"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Check validity of a conversation code."
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> ("code-check"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationCode
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Valid"]
                                                                                                                                                                                                                                                      ()))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V4
                                                                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                       'V4
                                                                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-code-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Delete conversation code"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                                                                                                                  Event]
                                                                                                                                                                                                                                                                              Event))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-code"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "remove-member"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation"
        (Summary "Get a conversation by ID"
         :> (From 'V6
             :> (MakesFederatedCall 'Galley "get-conversations"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (QualifiedCapture "cnv" ConvId
                                     :> Get '[JSON] Conversation))))))))
      :<|> (Named
              "get-conversation-roles"
              (Summary "Get existing roles available for the given conversation"
               :> (CanThrow 'ConvNotFound
                   :> (CanThrow 'ConvAccessDenied
                       :> (ZLocalUser
                           :> ("conversations"
                               :> (Capture "cnv" ConvId
                                   :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
            :<|> (Named
                    "get-group-info"
                    (Summary "Get MLS group information"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "query-group-info"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'MLSMissingGroupInfo
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("groupinfo"
                                                         :> MultiVerb
                                                              'GET
                                                              '[MLS]
                                                              '[Respond
                                                                  200
                                                                  "The group information"
                                                                  GroupInfoData]
                                                              GroupInfoData))))))))))
                  :<|> (Named
                          "list-conversation-ids-unqualified"
                          (Summary "[deprecated] Get all local conversation IDs."
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("ids"
                                           :> (QueryParam'
                                                 '[Optional, Strict,
                                                   Description
                                                     "Conversation ID to start from (exclusive)"]
                                                 "start"
                                                 ConvId
                                               :> (QueryParam'
                                                     '[Optional, Strict,
                                                       Description
                                                         "Maximum number of IDs to return"]
                                                     "size"
                                                     (Range 1 1000 Int32)
                                                   :> Get '[JSON] (ConversationList ConvId))))))))
                        :<|> (Named
                                "list-conversation-ids-v2"
                                (Summary "Get all conversation IDs."
                                 :> (Until 'V3
                                     :> (Description PaginationDocs
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list-ids"
                                                     :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                         :> Post '[JSON] ConvIdsPage)))))))
                              :<|> (Named
                                      "list-conversation-ids"
                                      (Summary "Get all conversation IDs."
                                       :> (From 'V3
                                           :> (Description PaginationDocs
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list-ids"
                                                           :> (ReqBody
                                                                 '[JSON] GetPaginatedConversationIds
                                                               :> Post '[JSON] ConvIdsPage)))))))
                                    :<|> (Named
                                            "get-conversations"
                                            (Summary "Get all *local* conversations."
                                             :> (Until 'V3
                                                 :> (Description
                                                       "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QueryParam'
                                                                   '[Optional, Strict,
                                                                     Description
                                                                       "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                                   "ids"
                                                                   (Range
                                                                      1
                                                                      32
                                                                      (CommaSeparatedList ConvId))
                                                                 :> (QueryParam'
                                                                       '[Optional, Strict,
                                                                         Description
                                                                           "Conversation ID to start from (exclusive)"]
                                                                       "start"
                                                                       ConvId
                                                                     :> (QueryParam'
                                                                           '[Optional, Strict,
                                                                             Description
                                                                               "Maximum number of conversations to return"]
                                                                           "size"
                                                                           (Range 1 500 Int32)
                                                                         :> MultiVerb
                                                                              'GET
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V2
                                                                                  200
                                                                                  "List of local conversations"
                                                                                  (ConversationList
                                                                                     Conversation)]
                                                                              (ConversationList
                                                                                 Conversation)))))))))
                                          :<|> (Named
                                                  "list-conversations@v1"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (Until 'V2
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list"
                                                                       :> ("v2"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> Post
                                                                                    '[JSON]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations@v2"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V2
                                                                 :> (Until 'V3
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("list"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V2
                                                                                              200
                                                                                              "Conversation page"
                                                                                              ConversationsResponse]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations@v5"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V3
                                                                       :> (Until 'V6
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("list"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ListConversations
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[VersionedRespond
                                                                                                    'V5
                                                                                                    200
                                                                                                    "Conversation page"
                                                                                                    ConversationsResponse]
                                                                                                ConversationsResponse))))))))
                                                            :<|> (Named
                                                                    "list-conversations"
                                                                    (Summary
                                                                       "Get conversation metadata for a list of conversation ids"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "get-conversations"
                                                                         :> (From 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("list"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ListConversations
                                                                                             :> Post
                                                                                                  '[JSON]
                                                                                                  ConversationsResponse)))))))
                                                                  :<|> (Named
                                                                          "get-conversation-by-reusable-code"
                                                                          (Summary
                                                                             "Get limited conversation information by key/code pair"
                                                                           :> (CanThrow
                                                                                 'CodeNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidConversationPassword
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (ZLocalUser
                                                                                                       :> ("conversations"
                                                                                                           :> ("join"
                                                                                                               :> (QueryParam'
                                                                                                                     '[Required,
                                                                                                                       Strict]
                                                                                                                     "key"
                                                                                                                     Key
                                                                                                                   :> (QueryParam'
                                                                                                                         '[Required,
                                                                                                                           Strict]
                                                                                                                         "code"
                                                                                                                         Value
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            ConversationCoverView))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v2"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (DescriptionOAuthScope
                                                                                       'WriteConversations
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "api-version"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (Until
                                                                                                       'V3
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'MLSNonEmptyMemberList
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                     :> (Description
                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZOptConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                           'V2
                                                                                                                                                           '[JSON]
                                                                                                                                                           NewConv
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     200
                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                     Conversation),
                                                                                                                                                                WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     201
                                                                                                                                                                     "Conversation created"
                                                                                                                                                                     Conversation)]
                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v3"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (DescriptionOAuthScope
                                                                                             'WriteConversations
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "api-version"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V3
                                                                                                           :> (Until
                                                                                                                 'V4
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNonEmptyMemberList
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                               :> (Description
                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZOptConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     NewConv
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V3
                                                                                                                                                                               200
                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                               Conversation),
                                                                                                                                                                          WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V3
                                                                                                                                                                               201
                                                                                                                                                                               "Conversation created"
                                                                                                                                                                               Conversation)]
                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                           Conversation)))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation@v5"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-not-fully-connected-backends"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V4
                                                                                                                 :> (Until
                                                                                                                       'V6
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNonEmptyMemberList
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       NonFederatingBackends
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           UnreachableBackends
                                                                                                                                                         :> (Description
                                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               NewConv
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V5
                                                                                                                                                                                         200
                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                         Conversation),
                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      CreateGroupConversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V5
                                                                                                                                                                                         201
                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                         CreateGroupConversation)]
                                                                                                                                                                                  CreateGroupConversationResponse)))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-group-conversation"
                                                                                                  (Summary
                                                                                                     "Create a new conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-not-fully-connected-backends"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-created"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (From
                                                                                                                         'V6
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNonEmptyMemberList
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (Description
                                                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 NewConv
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        Conversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V6
                                                                                                                                                                                           200
                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                           Conversation),
                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                        CreateGroupConversation
                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                           'V6
                                                                                                                                                                                           201
                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                                                    CreateGroupConversationResponse))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation@v2"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("self"
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V2
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V2
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (From
                                                                                                                     'V3
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("self"
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               Conversation)]
                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                           Conversation)))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-self-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("self"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-mls-self-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Get the user's MLS self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("mls-self"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[VersionedRespond
                                                                                                                                                            'V5
                                                                                                                                                            200
                                                                                                                                                            "The MLS self-conversation"
                                                                                                                                                            Conversation]
                                                                                                                                                        Conversation)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-mls-self-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Get the user's MLS self-conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("mls-self"
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "The MLS self-conversation"
                                                                                                                                                              Conversation]
                                                                                                                                                          Conversation))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get information about an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "get-sub-conversation"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSSubConvUnsupportedConvType
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "subconv"
                                                                                                                                                                                 SubConvId
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'GET
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[Respond
                                                                                                                                                                                        200
                                                                                                                                                                                        "Subconversation"
                                                                                                                                                                                        PublicSubConversation]
                                                                                                                                                                                    PublicSubConversation)))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "leave-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Leave an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "leave-sub-conversation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSProtocolErrorTag
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSStaleMessage
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZClient
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "subconv"
                                                                                                                                                                                                       SubConvId
                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "OK"]
                                                                                                                                                                                                              ()))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "delete-subconversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Delete an MLS subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "delete-sub-conversation"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSStaleMessage
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "subconv"
                                                                                                                                                                                                 SubConvId
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     DeleteSubConversationRequest
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Deletion successful"
                                                                                                                                                                                                            ()]
                                                                                                                                                                                                        ())))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-subconversation-group-info"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get MLS group information of subconversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "query-group-info"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSMissingGroupInfo
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("subconversations"
                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                   "subconv"
                                                                                                                                                                                                   SubConvId
                                                                                                                                                                                                 :> ("groupinfo"
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[MLS]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "The group information"
                                                                                                                                                                                                              GroupInfoData]
                                                                                                                                                                                                          GroupInfoData))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-one-to-one-conversation@v2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create a 1:1 conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "api-version"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-created"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V3
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NonBindingTeam
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         NewConv
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   200
                                                                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   201
                                                                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                                                                               Conversation))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-one-to-one-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create a 1:1 conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-created"
                                                                                                                                                                         :> (From
                                                                                                                                                                               'V3
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NonBindingTeam
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                     200
                                                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                     201
                                                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                                                 Conversation)))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V6
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                                        Conversation]
                                                                                                                                                                                                                    Conversation))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V6
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V7
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                                             MLSPublicKey)]
                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                         MLSPublicKey))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-one-to-one-mls-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V7
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> (QueryParam
                                                                                                                                                                                                                         "format"
                                                                                                                                                                                                                         MLSPublicKeyFormat
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                                   SomeKey)]
                                                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                                                               SomeKey))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               Invite
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "add-members-to-conversation"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V5
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "code-check"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Check validity of a conversation code."
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> ("code-check"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationCode
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Valid"]
                                                                                                                                                                                                                                                            ()))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V4
                                                                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                             'V4
                                                                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Delete conversation code"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                                                                                                                        Event]
                                                                                                                                                                                                                                                                                    Event))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-code"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "remove-member"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation-roles" ServerT
  (Summary "Get existing roles available for the given conversation"
   :> (CanThrow 'ConvNotFound
       :> (CanThrow 'ConvAccessDenied
           :> (ZLocalUser
               :> ("conversations"
                   :> (Capture "cnv" ConvId
                       :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get existing roles available for the given conversation"
            :> (CanThrow 'ConvNotFound
                :> (CanThrow 'ConvAccessDenied
                    :> (ZLocalUser
                        :> ("conversations"
                            :> (Capture "cnv" ConvId
                                :> ("roles" :> Get '[JSON] ConversationRolesList))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationRolesList
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r) =>
QualifiedWithTag 'QLocal UserId
-> ConvId -> Sem r ConversationRolesList
getConversationRoles
    API
  (Named
     "get-conversation-roles"
     (Summary "Get existing roles available for the given conversation"
      :> (CanThrow 'ConvNotFound
          :> (CanThrow 'ConvAccessDenied
              :> (ZLocalUser
                  :> ("conversations"
                      :> (Capture "cnv" ConvId
                          :> ("roles" :> Get '[JSON] ConversationRolesList))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-group-info"
        (Summary "Get MLS group information"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "query-group-info"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'MLSMissingGroupInfo
                         :> (CanThrow 'MLSNotEnabled
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("groupinfo"
                                             :> MultiVerb
                                                  'GET
                                                  '[MLS]
                                                  '[Respond
                                                      200 "The group information" GroupInfoData]
                                                  GroupInfoData))))))))))
      :<|> (Named
              "list-conversation-ids-unqualified"
              (Summary "[deprecated] Get all local conversation IDs."
               :> (Until 'V3
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("ids"
                               :> (QueryParam'
                                     '[Optional, Strict,
                                       Description "Conversation ID to start from (exclusive)"]
                                     "start"
                                     ConvId
                                   :> (QueryParam'
                                         '[Optional, Strict,
                                           Description "Maximum number of IDs to return"]
                                         "size"
                                         (Range 1 1000 Int32)
                                       :> Get '[JSON] (ConversationList ConvId))))))))
            :<|> (Named
                    "list-conversation-ids-v2"
                    (Summary "Get all conversation IDs."
                     :> (Until 'V3
                         :> (Description PaginationDocs
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list-ids"
                                         :> (ReqBody '[JSON] GetPaginatedConversationIds
                                             :> Post '[JSON] ConvIdsPage)))))))
                  :<|> (Named
                          "list-conversation-ids"
                          (Summary "Get all conversation IDs."
                           :> (From 'V3
                               :> (Description PaginationDocs
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list-ids"
                                               :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                   :> Post '[JSON] ConvIdsPage)))))))
                        :<|> (Named
                                "get-conversations"
                                (Summary "Get all *local* conversations."
                                 :> (Until 'V3
                                     :> (Description
                                           "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QueryParam'
                                                       '[Optional, Strict,
                                                         Description
                                                           "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                       "ids"
                                                       (Range 1 32 (CommaSeparatedList ConvId))
                                                     :> (QueryParam'
                                                           '[Optional, Strict,
                                                             Description
                                                               "Conversation ID to start from (exclusive)"]
                                                           "start"
                                                           ConvId
                                                         :> (QueryParam'
                                                               '[Optional, Strict,
                                                                 Description
                                                                   "Maximum number of conversations to return"]
                                                               "size"
                                                               (Range 1 500 Int32)
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V2
                                                                      200
                                                                      "List of local conversations"
                                                                      (ConversationList
                                                                         Conversation)]
                                                                  (ConversationList
                                                                     Conversation)))))))))
                              :<|> (Named
                                      "list-conversations@v1"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (Until 'V2
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list"
                                                           :> ("v2"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> Post
                                                                        '[JSON]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations@v2"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V2
                                                     :> (Until 'V3
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("list"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V2
                                                                                  200
                                                                                  "Conversation page"
                                                                                  ConversationsResponse]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations@v5"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V3
                                                           :> (Until 'V6
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("list"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V5
                                                                                        200
                                                                                        "Conversation page"
                                                                                        ConversationsResponse]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ListConversations
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      ConversationsResponse)))))))
                                                      :<|> (Named
                                                              "get-conversation-by-reusable-code"
                                                              (Summary
                                                                 "Get limited conversation information by key/code pair"
                                                               :> (CanThrow 'CodeNotFound
                                                                   :> (CanThrow
                                                                         'InvalidConversationPassword
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("join"
                                                                                                   :> (QueryParam'
                                                                                                         '[Required,
                                                                                                           Strict]
                                                                                                         "key"
                                                                                                         Key
                                                                                                       :> (QueryParam'
                                                                                                             '[Required,
                                                                                                               Strict]
                                                                                                             "code"
                                                                                                             Value
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                ConversationCoverView))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v2"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (DescriptionOAuthScope
                                                                           'WriteConversations
                                                                         :> (MakesFederatedCall
                                                                               'Brig "api-version"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (Until 'V3
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'MLSNonEmptyMemberList
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           UnreachableBackendsLegacy
                                                                                                                         :> (Description
                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZOptConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (VersionedReqBody
                                                                                                                                               'V2
                                                                                                                                               '[JSON]
                                                                                                                                               NewConv
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         200
                                                                                                                                                         "Conversation existed"
                                                                                                                                                         Conversation),
                                                                                                                                                    WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         201
                                                                                                                                                         "Conversation created"
                                                                                                                                                         Conversation)]
                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                     Conversation))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v3"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (DescriptionOAuthScope
                                                                                 'WriteConversations
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "api-version"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V3
                                                                                               :> (Until
                                                                                                     'V4
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSNonEmptyMemberList
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MissingLegalholdConsent
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                   :> (Description
                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZOptConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         NewConv
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V3
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V3
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   Conversation)]
                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                               Conversation)))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v5"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-not-fully-connected-backends"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V4
                                                                                                     :> (Until
                                                                                                           'V6
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                     :> (CanThrow
                                                                                                                                           NonFederatingBackends
                                                                                                                                         :> (CanThrow
                                                                                                                                               UnreachableBackends
                                                                                                                                             :> (Description
                                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   NewConv
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V5
                                                                                                                                                                             200
                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                             Conversation),
                                                                                                                                                                        WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          CreateGroupConversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V5
                                                                                                                                                                             201
                                                                                                                                                                             "Conversation created"
                                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                                      CreateGroupConversationResponse)))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-not-fully-connected-backends"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V6
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (Description
                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZOptConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     NewConv
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V6
                                                                                                                                                                               200
                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                               Conversation),
                                                                                                                                                                          WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            CreateGroupConversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V6
                                                                                                                                                                               201
                                                                                                                                                                               "Conversation created"
                                                                                                                                                                               CreateGroupConversation)]
                                                                                                                                                                        CreateGroupConversationResponse))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("self"
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V2
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V2
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (From
                                                                                                         'V3
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> ("self"
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   Conversation)]
                                                                                                                            (ResponseForExistedCreated
                                                                                                                               Conversation)))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("self"
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "get-mls-self-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Get the user's MLS self-conversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("mls-self"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[VersionedRespond
                                                                                                                                                'V5
                                                                                                                                                200
                                                                                                                                                "The MLS self-conversation"
                                                                                                                                                Conversation]
                                                                                                                                            Conversation)))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-mls-self-conversation"
                                                                                                                    (Summary
                                                                                                                       "Get the user's MLS self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("mls-self"
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "The MLS self-conversation"
                                                                                                                                                  Conversation]
                                                                                                                                              Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Get information about an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "get-sub-conversation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSSubConvUnsupportedConvType
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("subconversations"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "subconv"
                                                                                                                                                                     SubConvId
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'GET
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[Respond
                                                                                                                                                                            200
                                                                                                                                                                            "Subconversation"
                                                                                                                                                                            PublicSubConversation]
                                                                                                                                                                        PublicSubConversation)))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "leave-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Leave an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "leave-sub-conversation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSProtocolErrorTag
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSStaleMessage
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZClient
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "subconv"
                                                                                                                                                                                           SubConvId
                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "OK"]
                                                                                                                                                                                                  ()))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "delete-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Delete an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "delete-sub-conversation"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSStaleMessage
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "subconv"
                                                                                                                                                                                     SubConvId
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         DeleteSubConversationRequest
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'DELETE
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                200
                                                                                                                                                                                                "Deletion successful"
                                                                                                                                                                                                ()]
                                                                                                                                                                                            ())))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-subconversation-group-info"
                                                                                                                                            (Summary
                                                                                                                                               "Get MLS group information of subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "query-group-info"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSMissingGroupInfo
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "subconv"
                                                                                                                                                                                       SubConvId
                                                                                                                                                                                     :> ("groupinfo"
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[MLS]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "The group information"
                                                                                                                                                                                                  GroupInfoData]
                                                                                                                                                                                              GroupInfoData))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-one-to-one-conversation@v2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create a 1:1 conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "api-version"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-created"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V3
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       200
                                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       201
                                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-one-to-one-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create a 1:1 conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-created"
                                                                                                                                                             :> (From
                                                                                                                                                                   'V3
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NonBindingTeam
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               NewConv
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                         200
                                                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                         201
                                                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                                                     Conversation)))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation@v5"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V6
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                     UserId
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'GET
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[VersionedRespond
                                                                                                                                                                                                            'V5
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                            Conversation]
                                                                                                                                                                                                        Conversation))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V6
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V7
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                       UserId
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                 MLSPublicKey)]
                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                             MLSPublicKey))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V7
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> (QueryParam
                                                                                                                                                                                                             "format"
                                                                                                                                                                                                             MLSPublicKeyFormat
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                                       SomeKey)]
                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                   SomeKey))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   Invite
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation-unqualified2"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> ("v2"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V5
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Join a conversation using a reusable code"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "code-check"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Check validity of a conversation code."
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> ("code-check"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationCode
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Valid"]
                                                                                                                                                                                                                                                ()))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V4
                                                                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                 'V4
                                                                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Delete conversation code"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                                                                                                                            Event]
                                                                                                                                                                                                                                                                        Event))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-code"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get existing conversation code"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                                ())))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-member"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation-roles"
        (Summary "Get existing roles available for the given conversation"
         :> (CanThrow 'ConvNotFound
             :> (CanThrow 'ConvAccessDenied
                 :> (ZLocalUser
                     :> ("conversations"
                         :> (Capture "cnv" ConvId
                             :> ("roles" :> Get '[JSON] ConversationRolesList)))))))
      :<|> (Named
              "get-group-info"
              (Summary "Get MLS group information"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "query-group-info"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'MLSMissingGroupInfo
                               :> (CanThrow 'MLSNotEnabled
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("groupinfo"
                                                   :> MultiVerb
                                                        'GET
                                                        '[MLS]
                                                        '[Respond
                                                            200
                                                            "The group information"
                                                            GroupInfoData]
                                                        GroupInfoData))))))))))
            :<|> (Named
                    "list-conversation-ids-unqualified"
                    (Summary "[deprecated] Get all local conversation IDs."
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("ids"
                                     :> (QueryParam'
                                           '[Optional, Strict,
                                             Description
                                               "Conversation ID to start from (exclusive)"]
                                           "start"
                                           ConvId
                                         :> (QueryParam'
                                               '[Optional, Strict,
                                                 Description "Maximum number of IDs to return"]
                                               "size"
                                               (Range 1 1000 Int32)
                                             :> Get '[JSON] (ConversationList ConvId))))))))
                  :<|> (Named
                          "list-conversation-ids-v2"
                          (Summary "Get all conversation IDs."
                           :> (Until 'V3
                               :> (Description PaginationDocs
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list-ids"
                                               :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                   :> Post '[JSON] ConvIdsPage)))))))
                        :<|> (Named
                                "list-conversation-ids"
                                (Summary "Get all conversation IDs."
                                 :> (From 'V3
                                     :> (Description PaginationDocs
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list-ids"
                                                     :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                         :> Post '[JSON] ConvIdsPage)))))))
                              :<|> (Named
                                      "get-conversations"
                                      (Summary "Get all *local* conversations."
                                       :> (Until 'V3
                                           :> (Description
                                                 "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QueryParam'
                                                             '[Optional, Strict,
                                                               Description
                                                                 "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                             "ids"
                                                             (Range
                                                                1 32 (CommaSeparatedList ConvId))
                                                           :> (QueryParam'
                                                                 '[Optional, Strict,
                                                                   Description
                                                                     "Conversation ID to start from (exclusive)"]
                                                                 "start"
                                                                 ConvId
                                                               :> (QueryParam'
                                                                     '[Optional, Strict,
                                                                       Description
                                                                         "Maximum number of conversations to return"]
                                                                     "size"
                                                                     (Range 1 500 Int32)
                                                                   :> MultiVerb
                                                                        'GET
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V2
                                                                            200
                                                                            "List of local conversations"
                                                                            (ConversationList
                                                                               Conversation)]
                                                                        (ConversationList
                                                                           Conversation)))))))))
                                    :<|> (Named
                                            "list-conversations@v1"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (Until 'V2
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list"
                                                                 :> ("v2"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> Post
                                                                              '[JSON]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations@v2"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V2
                                                           :> (Until 'V3
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("list"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V2
                                                                                        200
                                                                                        "Conversation page"
                                                                                        ConversationsResponse]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations@v5"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V3
                                                                 :> (Until 'V6
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("list"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ListConversations
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[VersionedRespond
                                                                                              'V5
                                                                                              200
                                                                                              "Conversation page"
                                                                                              ConversationsResponse]
                                                                                          ConversationsResponse))))))))
                                                      :<|> (Named
                                                              "list-conversations"
                                                              (Summary
                                                                 "Get conversation metadata for a list of conversation ids"
                                                               :> (MakesFederatedCall
                                                                     'Galley "get-conversations"
                                                                   :> (From 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("list"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ListConversations
                                                                                       :> Post
                                                                                            '[JSON]
                                                                                            ConversationsResponse)))))))
                                                            :<|> (Named
                                                                    "get-conversation-by-reusable-code"
                                                                    (Summary
                                                                       "Get limited conversation information by key/code pair"
                                                                     :> (CanThrow 'CodeNotFound
                                                                         :> (CanThrow
                                                                               'InvalidConversationPassword
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> ("join"
                                                                                                         :> (QueryParam'
                                                                                                               '[Required,
                                                                                                                 Strict]
                                                                                                               "key"
                                                                                                               Key
                                                                                                             :> (QueryParam'
                                                                                                                   '[Required,
                                                                                                                     Strict]
                                                                                                                   "code"
                                                                                                                   Value
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      ConversationCoverView))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v2"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (DescriptionOAuthScope
                                                                                 'WriteConversations
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "api-version"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (Until
                                                                                                 'V3
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'MLSNonEmptyMemberList
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                               :> (Description
                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZOptConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                     'V2
                                                                                                                                                     '[JSON]
                                                                                                                                                     NewConv
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               200
                                                                                                                                                               "Conversation existed"
                                                                                                                                                               Conversation),
                                                                                                                                                          WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               201
                                                                                                                                                               "Conversation created"
                                                                                                                                                               Conversation)]
                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                           Conversation))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v3"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (DescriptionOAuthScope
                                                                                       'WriteConversations
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "api-version"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V3
                                                                                                     :> (Until
                                                                                                           'V4
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                         :> (Description
                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZOptConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               NewConv
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V3
                                                                                                                                                                         200
                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                         Conversation),
                                                                                                                                                                    WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V3
                                                                                                                                                                         201
                                                                                                                                                                         "Conversation created"
                                                                                                                                                                         Conversation)]
                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                     Conversation)))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation@v5"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-not-fully-connected-backends"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V4
                                                                                                           :> (Until
                                                                                                                 'V6
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNonEmptyMemberList
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                           :> (CanThrow
                                                                                                                                                 NonFederatingBackends
                                                                                                                                               :> (CanThrow
                                                                                                                                                     UnreachableBackends
                                                                                                                                                   :> (Description
                                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         NewConv
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V5
                                                                                                                                                                                   200
                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                   Conversation),
                                                                                                                                                                              WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                CreateGroupConversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V5
                                                                                                                                                                                   201
                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                   CreateGroupConversation)]
                                                                                                                                                                            CreateGroupConversationResponse)))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-group-conversation"
                                                                                            (Summary
                                                                                               "Create a new conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-not-fully-connected-backends"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-created"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (From
                                                                                                                   'V6
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNonEmptyMemberList
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (Description
                                                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           NewConv
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  Conversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V6
                                                                                                                                                                                     200
                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                     Conversation),
                                                                                                                                                                                WithHeaders
                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                  CreateGroupConversation
                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                     'V6
                                                                                                                                                                                     201
                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                                                              CreateGroupConversationResponse))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("self"
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V2
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V2
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (From
                                                                                                               'V3
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("self"
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         Conversation)]
                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                     Conversation)))))))
                                                                                                      :<|> (Named
                                                                                                              "create-self-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a self-conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("self"
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-mls-self-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Get the user's MLS self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("mls-self"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[VersionedRespond
                                                                                                                                                      'V5
                                                                                                                                                      200
                                                                                                                                                      "The MLS self-conversation"
                                                                                                                                                      Conversation]
                                                                                                                                                  Conversation)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-mls-self-conversation"
                                                                                                                          (Summary
                                                                                                                             "Get the user's MLS self-conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("mls-self"
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "The MLS self-conversation"
                                                                                                                                                        Conversation]
                                                                                                                                                    Conversation))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Get information about an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "get-sub-conversation"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSSubConvUnsupportedConvType
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "subconv"
                                                                                                                                                                           SubConvId
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'GET
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[Respond
                                                                                                                                                                                  200
                                                                                                                                                                                  "Subconversation"
                                                                                                                                                                                  PublicSubConversation]
                                                                                                                                                                              PublicSubConversation)))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "leave-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Leave an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "leave-sub-conversation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSProtocolErrorTag
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSStaleMessage
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZClient
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "subconv"
                                                                                                                                                                                                 SubConvId
                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "OK"]
                                                                                                                                                                                                        ()))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "delete-subconversation"
                                                                                                                                            (Summary
                                                                                                                                               "Delete an MLS subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "delete-sub-conversation"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSStaleMessage
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "subconv"
                                                                                                                                                                                           SubConvId
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               DeleteSubConversationRequest
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Deletion successful"
                                                                                                                                                                                                      ()]
                                                                                                                                                                                                  ())))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-subconversation-group-info"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get MLS group information of subconversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "query-group-info"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSMissingGroupInfo
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("subconversations"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "subconv"
                                                                                                                                                                                             SubConvId
                                                                                                                                                                                           :> ("groupinfo"
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[MLS]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "The group information"
                                                                                                                                                                                                        GroupInfoData]
                                                                                                                                                                                                    GroupInfoData))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-one-to-one-conversation@v2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create a 1:1 conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "api-version"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-created"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V3
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NonBindingTeam
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             200
                                                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             201
                                                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                                                                         Conversation))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-one-to-one-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create a 1:1 conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-created"
                                                                                                                                                                   :> (From
                                                                                                                                                                         'V3
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NonBindingTeam
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                               200
                                                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                               201
                                                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                                                           Conversation)))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation@v5"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V6
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                           UserId
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'GET
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                                  Conversation]
                                                                                                                                                                                                              Conversation))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V6
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V7
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                             UserId
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                                       MLSPublicKey)]
                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                   MLSPublicKey))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-one-to-one-mls-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V7
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> (QueryParam
                                                                                                                                                                                                                   "format"
                                                                                                                                                                                                                   MLSPublicKeyFormat
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                                             SomeKey)]
                                                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                                                         SomeKey))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         Invite
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation-unqualified2"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> ("v2"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "add-members-to-conversation"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V5
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Join a conversation using a reusable code"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "code-check"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Check validity of a conversation code."
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> ("code-check"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationCode
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Valid"]
                                                                                                                                                                                                                                                      ()))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V4
                                                                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                       'V4
                                                                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-code-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Delete conversation code"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                                                                                                                  Event]
                                                                                                                                                                                                                                                                              Event))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-code"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "remove-member"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-group-info" (((HasAnnotation 'Remote "galley" "query-group-info",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'MLSMissingGroupInfo ()),
        Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      GroupInfoData)
-> Dict (HasAnnotation 'Remote "galley" "query-group-info")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'MLSMissingGroupInfo ()),
        Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      GroupInfoData)
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error FederationError) r,
 Member FederatorAccess r, Member (Input Env) r,
 Member MemberStore r,
 Members
   '[Error (Tagged 'ConvNotFound ()),
     Error (Tagged 'MLSMissingGroupInfo ()),
     Error (Tagged 'MLSNotEnabled ())]
   r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> Sem r GroupInfoData
getGroupInfo))
    API
  (Named
     "get-group-info"
     (Summary "Get MLS group information"
      :> (From 'V5
          :> (MakesFederatedCall 'Galley "query-group-info"
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'MLSMissingGroupInfo
                      :> (CanThrow 'MLSNotEnabled
                          :> (ZLocalUser
                              :> ("conversations"
                                  :> (QualifiedCapture "cnv" ConvId
                                      :> ("groupinfo"
                                          :> MultiVerb
                                               'GET
                                               '[MLS]
                                               '[Respond 200 "The group information" GroupInfoData]
                                               GroupInfoData)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversation-ids-unqualified"
        (Summary "[deprecated] Get all local conversation IDs."
         :> (Until 'V3
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("ids"
                         :> (QueryParam'
                               '[Optional, Strict,
                                 Description "Conversation ID to start from (exclusive)"]
                               "start"
                               ConvId
                             :> (QueryParam'
                                   '[Optional, Strict,
                                     Description "Maximum number of IDs to return"]
                                   "size"
                                   (Range 1 1000 Int32)
                                 :> Get '[JSON] (ConversationList ConvId))))))))
      :<|> (Named
              "list-conversation-ids-v2"
              (Summary "Get all conversation IDs."
               :> (Until 'V3
                   :> (Description PaginationDocs
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list-ids"
                                   :> (ReqBody '[JSON] GetPaginatedConversationIds
                                       :> Post '[JSON] ConvIdsPage)))))))
            :<|> (Named
                    "list-conversation-ids"
                    (Summary "Get all conversation IDs."
                     :> (From 'V3
                         :> (Description PaginationDocs
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list-ids"
                                         :> (ReqBody '[JSON] GetPaginatedConversationIds
                                             :> Post '[JSON] ConvIdsPage)))))))
                  :<|> (Named
                          "get-conversations"
                          (Summary "Get all *local* conversations."
                           :> (Until 'V3
                               :> (Description
                                     "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QueryParam'
                                                 '[Optional, Strict,
                                                   Description
                                                     "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                 "ids"
                                                 (Range 1 32 (CommaSeparatedList ConvId))
                                               :> (QueryParam'
                                                     '[Optional, Strict,
                                                       Description
                                                         "Conversation ID to start from (exclusive)"]
                                                     "start"
                                                     ConvId
                                                   :> (QueryParam'
                                                         '[Optional, Strict,
                                                           Description
                                                             "Maximum number of conversations to return"]
                                                         "size"
                                                         (Range 1 500 Int32)
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V2
                                                                200
                                                                "List of local conversations"
                                                                (ConversationList Conversation)]
                                                            (ConversationList Conversation)))))))))
                        :<|> (Named
                                "list-conversations@v1"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (Until 'V2
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list"
                                                     :> ("v2"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> Post
                                                                  '[JSON]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations@v2"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V2
                                               :> (Until 'V3
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("list"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V2
                                                                            200
                                                                            "Conversation page"
                                                                            ConversationsResponse]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations@v5"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V3
                                                     :> (Until 'V6
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("list"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V5
                                                                                  200
                                                                                  "Conversation page"
                                                                                  ConversationsResponse]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ListConversations
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConversationsResponse)))))))
                                                :<|> (Named
                                                        "get-conversation-by-reusable-code"
                                                        (Summary
                                                           "Get limited conversation information by key/code pair"
                                                         :> (CanThrow 'CodeNotFound
                                                             :> (CanThrow
                                                                   'InvalidConversationPassword
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("join"
                                                                                             :> (QueryParam'
                                                                                                   '[Required,
                                                                                                     Strict]
                                                                                                   "key"
                                                                                                   Key
                                                                                                 :> (QueryParam'
                                                                                                       '[Required,
                                                                                                         Strict]
                                                                                                       "code"
                                                                                                       Value
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          ConversationCoverView))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v2"
                                                              (Summary "Create a new conversation"
                                                               :> (DescriptionOAuthScope
                                                                     'WriteConversations
                                                                   :> (MakesFederatedCall
                                                                         'Brig "api-version"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (Until 'V3
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'MLSNonEmptyMemberList
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     UnreachableBackendsLegacy
                                                                                                                   :> (Description
                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZOptConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (VersionedReqBody
                                                                                                                                         'V2
                                                                                                                                         '[JSON]
                                                                                                                                         NewConv
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   200
                                                                                                                                                   "Conversation existed"
                                                                                                                                                   Conversation),
                                                                                                                                              WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   201
                                                                                                                                                   "Conversation created"
                                                                                                                                                   Conversation)]
                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                               Conversation))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v3"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (DescriptionOAuthScope
                                                                           'WriteConversations
                                                                         :> (MakesFederatedCall
                                                                               'Brig "api-version"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V3
                                                                                         :> (Until
                                                                                               'V4
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSNonEmptyMemberList
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MissingLegalholdConsent
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackendsLegacy
                                                                                                                             :> (Description
                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZOptConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   NewConv
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V3
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V3
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             Conversation)]
                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                         Conversation)))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v5"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-not-fully-connected-backends"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V4
                                                                                               :> (Until
                                                                                                     'V6
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSNonEmptyMemberList
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MissingLegalholdConsent
                                                                                                                               :> (CanThrow
                                                                                                                                     NonFederatingBackends
                                                                                                                                   :> (CanThrow
                                                                                                                                         UnreachableBackends
                                                                                                                                       :> (Description
                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             NewConv
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       200
                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                       Conversation),
                                                                                                                                                                  WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    CreateGroupConversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       201
                                                                                                                                                                       "Conversation created"
                                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                                CreateGroupConversationResponse)))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-not-fully-connected-backends"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V6
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'MLSNonEmptyMemberList
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (Description
                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZOptConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               NewConv
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         200
                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                         Conversation),
                                                                                                                                                                    WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      CreateGroupConversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         201
                                                                                                                                                                         "Conversation created"
                                                                                                                                                                         CreateGroupConversation)]
                                                                                                                                                                  CreateGroupConversationResponse))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (Until 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("self"
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V2
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V2
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation@v5"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (From
                                                                                                   'V3
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> ("self"
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             Conversation)]
                                                                                                                      (ResponseForExistedCreated
                                                                                                                         Conversation)))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("self"
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "get-mls-self-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Get the user's MLS self-conversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("mls-self"
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[VersionedRespond
                                                                                                                                          'V5
                                                                                                                                          200
                                                                                                                                          "The MLS self-conversation"
                                                                                                                                          Conversation]
                                                                                                                                      Conversation)))))))
                                                                                                      :<|> (Named
                                                                                                              "get-mls-self-conversation"
                                                                                                              (Summary
                                                                                                                 "Get the user's MLS self-conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("mls-self"
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "The MLS self-conversation"
                                                                                                                                            Conversation]
                                                                                                                                        Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Get information about an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "get-sub-conversation"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSSubConvUnsupportedConvType
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("subconversations"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "subconv"
                                                                                                                                                               SubConvId
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'GET
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[Respond
                                                                                                                                                                      200
                                                                                                                                                                      "Subconversation"
                                                                                                                                                                      PublicSubConversation]
                                                                                                                                                                  PublicSubConversation)))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "leave-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Leave an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "leave-sub-conversation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSProtocolErrorTag
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSStaleMessage
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZClient
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "subconv"
                                                                                                                                                                                     SubConvId
                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'DELETE
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "OK"]
                                                                                                                                                                                            ()))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "delete-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Delete an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "delete-sub-conversation"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSStaleMessage
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "subconv"
                                                                                                                                                                               SubConvId
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   DeleteSubConversationRequest
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'DELETE
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[Respond
                                                                                                                                                                                          200
                                                                                                                                                                                          "Deletion successful"
                                                                                                                                                                                          ()]
                                                                                                                                                                                      ())))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-subconversation-group-info"
                                                                                                                                      (Summary
                                                                                                                                         "Get MLS group information of subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "query-group-info"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSMissingGroupInfo
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "subconv"
                                                                                                                                                                                 SubConvId
                                                                                                                                                                               :> ("groupinfo"
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[MLS]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "The group information"
                                                                                                                                                                                            GroupInfoData]
                                                                                                                                                                                        GroupInfoData))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-one-to-one-conversation@v2"
                                                                                                                                            (Summary
                                                                                                                                               "Create a 1:1 conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "api-version"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-created"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V3
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NonBindingTeam
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 200
                                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 201
                                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-one-to-one-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create a 1:1 conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-created"
                                                                                                                                                       :> (From
                                                                                                                                                             'V3
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NonBindingTeam
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         NewConv
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                   200
                                                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                   201
                                                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                                                               Conversation)))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation@v5"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V6
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "usr"
                                                                                                                                                                                               UserId
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'GET
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[VersionedRespond
                                                                                                                                                                                                      'V5
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                      Conversation]
                                                                                                                                                                                                  Conversation))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation@v6"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V6
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V7
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                 UserId
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                           MLSPublicKey)]
                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                       MLSPublicKey))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V7
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> (QueryParam
                                                                                                                                                                                                       "format"
                                                                                                                                                                                                       MLSPublicKeyFormat
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                 SomeKey)]
                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                             SomeKey))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add members to an existing conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             Invite
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation-unqualified2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> ("v2"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (From
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "join-conversation-by-id-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V5
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Join a conversation using a reusable code"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "code-check"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Check validity of a conversation code."
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> ("code-check"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationCode
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Valid"]
                                                                                                                                                                                                                                          ()))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V4
                                                                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                           'V4
                                                                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Delete conversation code"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                                                                                                                      Event]
                                                                                                                                                                                                                                                                  Event))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-code"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get existing conversation code"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "member-typing-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                                          ())))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-member"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-other-member"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-group-info"
        (Summary "Get MLS group information"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "query-group-info"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'MLSMissingGroupInfo
                         :> (CanThrow 'MLSNotEnabled
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("groupinfo"
                                             :> MultiVerb
                                                  'GET
                                                  '[MLS]
                                                  '[Respond
                                                      200 "The group information" GroupInfoData]
                                                  GroupInfoData))))))))))
      :<|> (Named
              "list-conversation-ids-unqualified"
              (Summary "[deprecated] Get all local conversation IDs."
               :> (Until 'V3
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("ids"
                               :> (QueryParam'
                                     '[Optional, Strict,
                                       Description "Conversation ID to start from (exclusive)"]
                                     "start"
                                     ConvId
                                   :> (QueryParam'
                                         '[Optional, Strict,
                                           Description "Maximum number of IDs to return"]
                                         "size"
                                         (Range 1 1000 Int32)
                                       :> Get '[JSON] (ConversationList ConvId))))))))
            :<|> (Named
                    "list-conversation-ids-v2"
                    (Summary "Get all conversation IDs."
                     :> (Until 'V3
                         :> (Description PaginationDocs
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list-ids"
                                         :> (ReqBody '[JSON] GetPaginatedConversationIds
                                             :> Post '[JSON] ConvIdsPage)))))))
                  :<|> (Named
                          "list-conversation-ids"
                          (Summary "Get all conversation IDs."
                           :> (From 'V3
                               :> (Description PaginationDocs
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list-ids"
                                               :> (ReqBody '[JSON] GetPaginatedConversationIds
                                                   :> Post '[JSON] ConvIdsPage)))))))
                        :<|> (Named
                                "get-conversations"
                                (Summary "Get all *local* conversations."
                                 :> (Until 'V3
                                     :> (Description
                                           "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QueryParam'
                                                       '[Optional, Strict,
                                                         Description
                                                           "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                       "ids"
                                                       (Range 1 32 (CommaSeparatedList ConvId))
                                                     :> (QueryParam'
                                                           '[Optional, Strict,
                                                             Description
                                                               "Conversation ID to start from (exclusive)"]
                                                           "start"
                                                           ConvId
                                                         :> (QueryParam'
                                                               '[Optional, Strict,
                                                                 Description
                                                                   "Maximum number of conversations to return"]
                                                               "size"
                                                               (Range 1 500 Int32)
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V2
                                                                      200
                                                                      "List of local conversations"
                                                                      (ConversationList
                                                                         Conversation)]
                                                                  (ConversationList
                                                                     Conversation)))))))))
                              :<|> (Named
                                      "list-conversations@v1"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (Until 'V2
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list"
                                                           :> ("v2"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> Post
                                                                        '[JSON]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations@v2"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V2
                                                     :> (Until 'V3
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("list"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V2
                                                                                  200
                                                                                  "Conversation page"
                                                                                  ConversationsResponse]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations@v5"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V3
                                                           :> (Until 'V6
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("list"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ListConversations
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[VersionedRespond
                                                                                        'V5
                                                                                        200
                                                                                        "Conversation page"
                                                                                        ConversationsResponse]
                                                                                    ConversationsResponse))))))))
                                                :<|> (Named
                                                        "list-conversations"
                                                        (Summary
                                                           "Get conversation metadata for a list of conversation ids"
                                                         :> (MakesFederatedCall
                                                               'Galley "get-conversations"
                                                             :> (From 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("list"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ListConversations
                                                                                 :> Post
                                                                                      '[JSON]
                                                                                      ConversationsResponse)))))))
                                                      :<|> (Named
                                                              "get-conversation-by-reusable-code"
                                                              (Summary
                                                                 "Get limited conversation information by key/code pair"
                                                               :> (CanThrow 'CodeNotFound
                                                                   :> (CanThrow
                                                                         'InvalidConversationPassword
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> ("join"
                                                                                                   :> (QueryParam'
                                                                                                         '[Required,
                                                                                                           Strict]
                                                                                                         "key"
                                                                                                         Key
                                                                                                       :> (QueryParam'
                                                                                                             '[Required,
                                                                                                               Strict]
                                                                                                             "code"
                                                                                                             Value
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                ConversationCoverView))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v2"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (DescriptionOAuthScope
                                                                           'WriteConversations
                                                                         :> (MakesFederatedCall
                                                                               'Brig "api-version"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (Until 'V3
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'MLSNonEmptyMemberList
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           UnreachableBackendsLegacy
                                                                                                                         :> (Description
                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZOptConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (VersionedReqBody
                                                                                                                                               'V2
                                                                                                                                               '[JSON]
                                                                                                                                               NewConv
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         200
                                                                                                                                                         "Conversation existed"
                                                                                                                                                         Conversation),
                                                                                                                                                    WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         201
                                                                                                                                                         "Conversation created"
                                                                                                                                                         Conversation)]
                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                     Conversation))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v3"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (DescriptionOAuthScope
                                                                                 'WriteConversations
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "api-version"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V3
                                                                                               :> (Until
                                                                                                     'V4
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSNonEmptyMemberList
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MissingLegalholdConsent
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                   :> (Description
                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZOptConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         NewConv
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V3
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V3
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   Conversation)]
                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                               Conversation)))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation@v5"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-not-fully-connected-backends"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V4
                                                                                                     :> (Until
                                                                                                           'V6
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNonEmptyMemberList
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                     :> (CanThrow
                                                                                                                                           NonFederatingBackends
                                                                                                                                         :> (CanThrow
                                                                                                                                               UnreachableBackends
                                                                                                                                             :> (Description
                                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   NewConv
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V5
                                                                                                                                                                             200
                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                             Conversation),
                                                                                                                                                                        WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          CreateGroupConversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V5
                                                                                                                                                                             201
                                                                                                                                                                             "Conversation created"
                                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                                      CreateGroupConversationResponse)))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-group-conversation"
                                                                                      (Summary
                                                                                         "Create a new conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-not-fully-connected-backends"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-created"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (From
                                                                                                             'V6
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNonEmptyMemberList
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (Description
                                                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZOptConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     NewConv
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            Conversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V6
                                                                                                                                                                               200
                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                               Conversation),
                                                                                                                                                                          WithHeaders
                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                            CreateGroupConversation
                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                               'V6
                                                                                                                                                                               201
                                                                                                                                                                               "Conversation created"
                                                                                                                                                                               CreateGroupConversation)]
                                                                                                                                                                        CreateGroupConversationResponse))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("self"
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V2
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V2
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (From
                                                                                                         'V3
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> ("self"
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   Conversation)]
                                                                                                                            (ResponseForExistedCreated
                                                                                                                               Conversation)))))))
                                                                                                :<|> (Named
                                                                                                        "create-self-conversation"
                                                                                                        (Summary
                                                                                                           "Create a self-conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("self"
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "get-mls-self-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Get the user's MLS self-conversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("mls-self"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[VersionedRespond
                                                                                                                                                'V5
                                                                                                                                                200
                                                                                                                                                "The MLS self-conversation"
                                                                                                                                                Conversation]
                                                                                                                                            Conversation)))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-mls-self-conversation"
                                                                                                                    (Summary
                                                                                                                       "Get the user's MLS self-conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("mls-self"
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "The MLS self-conversation"
                                                                                                                                                  Conversation]
                                                                                                                                              Conversation))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Get information about an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "get-sub-conversation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSSubConvUnsupportedConvType
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("subconversations"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "subconv"
                                                                                                                                                                     SubConvId
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'GET
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[Respond
                                                                                                                                                                            200
                                                                                                                                                                            "Subconversation"
                                                                                                                                                                            PublicSubConversation]
                                                                                                                                                                        PublicSubConversation)))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "leave-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Leave an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "leave-sub-conversation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSProtocolErrorTag
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSStaleMessage
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZClient
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "subconv"
                                                                                                                                                                                           SubConvId
                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "OK"]
                                                                                                                                                                                                  ()))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "delete-subconversation"
                                                                                                                                      (Summary
                                                                                                                                         "Delete an MLS subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "delete-sub-conversation"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSStaleMessage
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "subconv"
                                                                                                                                                                                     SubConvId
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         DeleteSubConversationRequest
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'DELETE
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                200
                                                                                                                                                                                                "Deletion successful"
                                                                                                                                                                                                ()]
                                                                                                                                                                                            ())))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-subconversation-group-info"
                                                                                                                                            (Summary
                                                                                                                                               "Get MLS group information of subconversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "query-group-info"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSMissingGroupInfo
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("subconversations"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "subconv"
                                                                                                                                                                                       SubConvId
                                                                                                                                                                                     :> ("groupinfo"
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[MLS]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "The group information"
                                                                                                                                                                                                  GroupInfoData]
                                                                                                                                                                                              GroupInfoData))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-one-to-one-conversation@v2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create a 1:1 conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "api-version"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-created"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V3
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       200
                                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       201
                                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-one-to-one-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create a 1:1 conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-created"
                                                                                                                                                             :> (From
                                                                                                                                                                   'V3
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NonBindingTeam
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               NewConv
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                         200
                                                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                         201
                                                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                                                     Conversation)))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation@v5"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V6
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                     UserId
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'GET
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[VersionedRespond
                                                                                                                                                                                                            'V5
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                                            Conversation]
                                                                                                                                                                                                        Conversation))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation@v6"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V6
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V7
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                       UserId
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                 MLSPublicKey)]
                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                             MLSPublicKey))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-one-to-one-mls-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V7
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> (QueryParam
                                                                                                                                                                                                             "format"
                                                                                                                                                                                                             MLSPublicKeyFormat
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                                       SomeKey)]
                                                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                                                   SomeKey))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   Invite
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation-unqualified2"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> ("v2"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "add-members-to-conversation"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V5
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Join a conversation using a reusable code"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "code-check"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Check validity of a conversation code."
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> ("code-check"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationCode
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Valid"]
                                                                                                                                                                                                                                                ()))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V4
                                                                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                 'V4
                                                                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-code-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Delete conversation code"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                                                                                                                            Event]
                                                                                                                                                                                                                                                                        Event))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-code"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get existing conversation code"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                                ())))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "remove-member"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversation-ids-unqualified" ServerT
  (Summary "[deprecated] Get all local conversation IDs."
   :> (Until 'V3
       :> (ZLocalUser
           :> ("conversations"
               :> ("ids"
                   :> (QueryParam'
                         '[Optional, Strict,
                           Description "Conversation ID to start from (exclusive)"]
                         "start"
                         ConvId
                       :> (QueryParam'
                             '[Optional, Strict, Description "Maximum number of IDs to return"]
                             "size"
                             (Range 1 1000 Int32)
                           :> Get '[JSON] (ConversationList ConvId))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get all local conversation IDs."
            :> (Until 'V3
                :> (ZLocalUser
                    :> ("conversations"
                        :> ("ids"
                            :> (QueryParam'
                                  '[Optional, Strict,
                                    Description "Conversation ID to start from (exclusive)"]
                                  "start"
                                  ConvId
                                :> (QueryParam'
                                      '[Optional, Strict,
                                        Description "Maximum number of IDs to return"]
                                      "size"
                                      (Range 1 1000 Int32)
                                    :> Get '[JSON] (ConversationList ConvId)))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Maybe ConvId
-> Maybe (Range 1 1000 Int32)
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationList ConvId)
forall (r :: EffectRow).
Member (ListItems LegacyPaging ConvId) r =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConvId
-> Maybe (Range 1 1000 Int32)
-> Sem r (ConversationList ConvId)
conversationIdsPageFromUnqualified
    API
  (Named
     "list-conversation-ids-unqualified"
     (Summary "[deprecated] Get all local conversation IDs."
      :> (Until 'V3
          :> (ZLocalUser
              :> ("conversations"
                  :> ("ids"
                      :> (QueryParam'
                            '[Optional, Strict,
                              Description "Conversation ID to start from (exclusive)"]
                            "start"
                            ConvId
                          :> (QueryParam'
                                '[Optional, Strict, Description "Maximum number of IDs to return"]
                                "size"
                                (Range 1 1000 Int32)
                              :> Get '[JSON] (ConversationList ConvId)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversation-ids-v2"
        (Summary "Get all conversation IDs."
         :> (Until 'V3
             :> (Description PaginationDocs
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list-ids"
                             :> (ReqBody '[JSON] GetPaginatedConversationIds
                                 :> Post '[JSON] ConvIdsPage)))))))
      :<|> (Named
              "list-conversation-ids"
              (Summary "Get all conversation IDs."
               :> (From 'V3
                   :> (Description PaginationDocs
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list-ids"
                                   :> (ReqBody '[JSON] GetPaginatedConversationIds
                                       :> Post '[JSON] ConvIdsPage)))))))
            :<|> (Named
                    "get-conversations"
                    (Summary "Get all *local* conversations."
                     :> (Until 'V3
                         :> (Description
                               "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QueryParam'
                                           '[Optional, Strict,
                                             Description
                                               "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                           "ids"
                                           (Range 1 32 (CommaSeparatedList ConvId))
                                         :> (QueryParam'
                                               '[Optional, Strict,
                                                 Description
                                                   "Conversation ID to start from (exclusive)"]
                                               "start"
                                               ConvId
                                             :> (QueryParam'
                                                   '[Optional, Strict,
                                                     Description
                                                       "Maximum number of conversations to return"]
                                                   "size"
                                                   (Range 1 500 Int32)
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V2
                                                          200
                                                          "List of local conversations"
                                                          (ConversationList Conversation)]
                                                      (ConversationList Conversation)))))))))
                  :<|> (Named
                          "list-conversations@v1"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (Until 'V2
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list"
                                               :> ("v2"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> Post '[JSON] ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations@v2"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V2
                                         :> (Until 'V3
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("list"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V2
                                                                      200
                                                                      "Conversation page"
                                                                      ConversationsResponse]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations@v5"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V3
                                               :> (Until 'V6
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("list"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V5
                                                                            200
                                                                            "Conversation page"
                                                                            ConversationsResponse]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list"
                                                                 :> (ReqBody
                                                                       '[JSON] ListConversations
                                                                     :> Post
                                                                          '[JSON]
                                                                          ConversationsResponse)))))))
                                          :<|> (Named
                                                  "get-conversation-by-reusable-code"
                                                  (Summary
                                                     "Get limited conversation information by key/code pair"
                                                   :> (CanThrow 'CodeNotFound
                                                       :> (CanThrow 'InvalidConversationPassword
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("join"
                                                                                       :> (QueryParam'
                                                                                             '[Required,
                                                                                               Strict]
                                                                                             "key"
                                                                                             Key
                                                                                           :> (QueryParam'
                                                                                                 '[Required,
                                                                                                   Strict]
                                                                                                 "code"
                                                                                                 Value
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    ConversationCoverView))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v2"
                                                        (Summary "Create a new conversation"
                                                         :> (DescriptionOAuthScope
                                                               'WriteConversations
                                                             :> (MakesFederatedCall
                                                                   'Brig "api-version"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (Until 'V3
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'MLSNonEmptyMemberList
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               UnreachableBackendsLegacy
                                                                                                             :> (Description
                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZOptConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (VersionedReqBody
                                                                                                                                   'V2
                                                                                                                                   '[JSON]
                                                                                                                                   NewConv
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             200
                                                                                                                                             "Conversation existed"
                                                                                                                                             Conversation),
                                                                                                                                        WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             201
                                                                                                                                             "Conversation created"
                                                                                                                                             Conversation)]
                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                         Conversation))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v3"
                                                              (Summary "Create a new conversation"
                                                               :> (DescriptionOAuthScope
                                                                     'WriteConversations
                                                                   :> (MakesFederatedCall
                                                                         'Brig "api-version"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V3
                                                                                   :> (Until 'V4
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSNonEmptyMemberList
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MissingLegalholdConsent
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackendsLegacy
                                                                                                                       :> (Description
                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZOptConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             NewConv
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V3
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V3
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation)))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v5"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-not-fully-connected-backends"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V4
                                                                                         :> (Until
                                                                                               'V6
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSNonEmptyMemberList
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MissingLegalholdConsent
                                                                                                                         :> (CanThrow
                                                                                                                               NonFederatingBackends
                                                                                                                             :> (CanThrow
                                                                                                                                   UnreachableBackends
                                                                                                                                 :> (Description
                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       NewConv
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              CreateGroupConversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                                          CreateGroupConversationResponse)))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-not-fully-connected-backends"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V6
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'MLSNonEmptyMemberList
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (Description
                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZOptConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         NewConv
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                CreateGroupConversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   CreateGroupConversation)]
                                                                                                                                                            CreateGroupConversationResponse))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation@v2"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (Until 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("self"
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V2
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V2
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation@v5"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (From 'V3
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("self"
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       Conversation)]
                                                                                                                (ResponseForExistedCreated
                                                                                                                   Conversation)))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("self"
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "get-mls-self-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Get the user's MLS self-conversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> ("mls-self"
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[VersionedRespond
                                                                                                                                    'V5
                                                                                                                                    200
                                                                                                                                    "The MLS self-conversation"
                                                                                                                                    Conversation]
                                                                                                                                Conversation)))))))
                                                                                                :<|> (Named
                                                                                                        "get-mls-self-conversation"
                                                                                                        (Summary
                                                                                                           "Get the user's MLS self-conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("mls-self"
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "The MLS self-conversation"
                                                                                                                                      Conversation]
                                                                                                                                  Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "get-subconversation"
                                                                                                              (Summary
                                                                                                                 "Get information about an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "get-sub-conversation"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSSubConvUnsupportedConvType
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("subconversations"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "subconv"
                                                                                                                                                         SubConvId
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'GET
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[Respond
                                                                                                                                                                200
                                                                                                                                                                "Subconversation"
                                                                                                                                                                PublicSubConversation]
                                                                                                                                                            PublicSubConversation)))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "leave-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Leave an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "leave-sub-conversation"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSProtocolErrorTag
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSStaleMessage
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZClient
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "subconv"
                                                                                                                                                                               SubConvId
                                                                                                                                                                             :> ("self"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'DELETE
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "OK"]
                                                                                                                                                                                      ()))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "delete-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Delete an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "delete-sub-conversation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSStaleMessage
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "subconv"
                                                                                                                                                                         SubConvId
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             DeleteSubConversationRequest
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'DELETE
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[Respond
                                                                                                                                                                                    200
                                                                                                                                                                                    "Deletion successful"
                                                                                                                                                                                    ()]
                                                                                                                                                                                ())))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-subconversation-group-info"
                                                                                                                                (Summary
                                                                                                                                   "Get MLS group information of subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "query-group-info"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSMissingGroupInfo
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "subconv"
                                                                                                                                                                           SubConvId
                                                                                                                                                                         :> ("groupinfo"
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[MLS]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "The group information"
                                                                                                                                                                                      GroupInfoData]
                                                                                                                                                                                  GroupInfoData))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-one-to-one-conversation@v2"
                                                                                                                                      (Summary
                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "api-version"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-created"
                                                                                                                                               :> (Until
                                                                                                                                                     'V3
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NonBindingTeam
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotConnected
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 OperationDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 NewConv
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           200
                                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           201
                                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-one-to-one-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Create a 1:1 conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-created"
                                                                                                                                                 :> (From
                                                                                                                                                       'V3
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NonBindingTeam
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                             200
                                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                             201
                                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                                                         Conversation)))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation@v5"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (Until
                                                                                                                                                             'V6
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSFederatedOne2OneNotSupported
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "usr"
                                                                                                                                                                                         UserId
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'GET
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[VersionedRespond
                                                                                                                                                                                                'V5
                                                                                                                                                                                                200
                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                Conversation]
                                                                                                                                                                                            Conversation))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation@v6"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V6
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V7
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "usr"
                                                                                                                                                                                           UserId
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                     MLSPublicKey)]
                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                 MLSPublicKey))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V7
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotConnected
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> (QueryParam
                                                                                                                                                                                                 "format"
                                                                                                                                                                                                 MLSPublicKeyFormat
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                           SomeKey)]
                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                       SomeKey))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add members to an existing conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       Invite
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation-unqualified2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> ("v2"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (From
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "join-conversation-by-id-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V5
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "join-conversation-by-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Join a conversation using a reusable code"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           JoinConversationByCode
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "code-check"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Check validity of a conversation code."
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> ("code-check"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationCode
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Valid"]
                                                                                                                                                                                                                                    ()))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V4
                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "create-conversation-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                     'V4
                                                                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Delete conversation code"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'DELETE
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                                                                                                                Event]
                                                                                                                                                                                                                                                            Event))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-code"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get existing conversation code"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "member-typing-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                                    ())))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "member-typing-qualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-member"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-other-member"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversation-ids-unqualified"
        (Summary "[deprecated] Get all local conversation IDs."
         :> (Until 'V3
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("ids"
                         :> (QueryParam'
                               '[Optional, Strict,
                                 Description "Conversation ID to start from (exclusive)"]
                               "start"
                               ConvId
                             :> (QueryParam'
                                   '[Optional, Strict,
                                     Description "Maximum number of IDs to return"]
                                   "size"
                                   (Range 1 1000 Int32)
                                 :> Get '[JSON] (ConversationList ConvId))))))))
      :<|> (Named
              "list-conversation-ids-v2"
              (Summary "Get all conversation IDs."
               :> (Until 'V3
                   :> (Description PaginationDocs
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list-ids"
                                   :> (ReqBody '[JSON] GetPaginatedConversationIds
                                       :> Post '[JSON] ConvIdsPage)))))))
            :<|> (Named
                    "list-conversation-ids"
                    (Summary "Get all conversation IDs."
                     :> (From 'V3
                         :> (Description PaginationDocs
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list-ids"
                                         :> (ReqBody '[JSON] GetPaginatedConversationIds
                                             :> Post '[JSON] ConvIdsPage)))))))
                  :<|> (Named
                          "get-conversations"
                          (Summary "Get all *local* conversations."
                           :> (Until 'V3
                               :> (Description
                                     "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QueryParam'
                                                 '[Optional, Strict,
                                                   Description
                                                     "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                                 "ids"
                                                 (Range 1 32 (CommaSeparatedList ConvId))
                                               :> (QueryParam'
                                                     '[Optional, Strict,
                                                       Description
                                                         "Conversation ID to start from (exclusive)"]
                                                     "start"
                                                     ConvId
                                                   :> (QueryParam'
                                                         '[Optional, Strict,
                                                           Description
                                                             "Maximum number of conversations to return"]
                                                         "size"
                                                         (Range 1 500 Int32)
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V2
                                                                200
                                                                "List of local conversations"
                                                                (ConversationList Conversation)]
                                                            (ConversationList Conversation)))))))))
                        :<|> (Named
                                "list-conversations@v1"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (Until 'V2
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list"
                                                     :> ("v2"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> Post
                                                                  '[JSON]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations@v2"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V2
                                               :> (Until 'V3
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("list"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V2
                                                                            200
                                                                            "Conversation page"
                                                                            ConversationsResponse]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations@v5"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V3
                                                     :> (Until 'V6
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("list"
                                                                     :> (ReqBody
                                                                           '[JSON] ListConversations
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[VersionedRespond
                                                                                  'V5
                                                                                  200
                                                                                  "Conversation page"
                                                                                  ConversationsResponse]
                                                                              ConversationsResponse))))))))
                                          :<|> (Named
                                                  "list-conversations"
                                                  (Summary
                                                     "Get conversation metadata for a list of conversation ids"
                                                   :> (MakesFederatedCall
                                                         'Galley "get-conversations"
                                                       :> (From 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("list"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ListConversations
                                                                           :> Post
                                                                                '[JSON]
                                                                                ConversationsResponse)))))))
                                                :<|> (Named
                                                        "get-conversation-by-reusable-code"
                                                        (Summary
                                                           "Get limited conversation information by key/code pair"
                                                         :> (CanThrow 'CodeNotFound
                                                             :> (CanThrow
                                                                   'InvalidConversationPassword
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> ("join"
                                                                                             :> (QueryParam'
                                                                                                   '[Required,
                                                                                                     Strict]
                                                                                                   "key"
                                                                                                   Key
                                                                                                 :> (QueryParam'
                                                                                                       '[Required,
                                                                                                         Strict]
                                                                                                       "code"
                                                                                                       Value
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          ConversationCoverView))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v2"
                                                              (Summary "Create a new conversation"
                                                               :> (DescriptionOAuthScope
                                                                     'WriteConversations
                                                                   :> (MakesFederatedCall
                                                                         'Brig "api-version"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (Until 'V3
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'MLSNonEmptyMemberList
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     UnreachableBackendsLegacy
                                                                                                                   :> (Description
                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZOptConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (VersionedReqBody
                                                                                                                                         'V2
                                                                                                                                         '[JSON]
                                                                                                                                         NewConv
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   200
                                                                                                                                                   "Conversation existed"
                                                                                                                                                   Conversation),
                                                                                                                                              WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   201
                                                                                                                                                   "Conversation created"
                                                                                                                                                   Conversation)]
                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                               Conversation))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v3"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (DescriptionOAuthScope
                                                                           'WriteConversations
                                                                         :> (MakesFederatedCall
                                                                               'Brig "api-version"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V3
                                                                                         :> (Until
                                                                                               'V4
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSNonEmptyMemberList
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MissingLegalholdConsent
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackendsLegacy
                                                                                                                             :> (Description
                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZOptConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   NewConv
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V3
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V3
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             Conversation)]
                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                         Conversation)))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation@v5"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-not-fully-connected-backends"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V4
                                                                                               :> (Until
                                                                                                     'V6
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSNonEmptyMemberList
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'MissingLegalholdConsent
                                                                                                                               :> (CanThrow
                                                                                                                                     NonFederatingBackends
                                                                                                                                   :> (CanThrow
                                                                                                                                         UnreachableBackends
                                                                                                                                       :> (Description
                                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             NewConv
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       200
                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                       Conversation),
                                                                                                                                                                  WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    CreateGroupConversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V5
                                                                                                                                                                       201
                                                                                                                                                                       "Conversation created"
                                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                                CreateGroupConversationResponse)))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-group-conversation"
                                                                                (Summary
                                                                                   "Create a new conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-not-fully-connected-backends"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-created"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (From
                                                                                                       'V6
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'MLSNonEmptyMemberList
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (Description
                                                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZOptConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               NewConv
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      Conversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         200
                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                         Conversation),
                                                                                                                                                                    WithHeaders
                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                      CreateGroupConversation
                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                         'V6
                                                                                                                                                                         201
                                                                                                                                                                         "Conversation created"
                                                                                                                                                                         CreateGroupConversation)]
                                                                                                                                                                  CreateGroupConversationResponse))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (Until 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("self"
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V2
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V2
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation@v5"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (From
                                                                                                   'V3
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> ("self"
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             Conversation)]
                                                                                                                      (ResponseForExistedCreated
                                                                                                                         Conversation)))))))
                                                                                          :<|> (Named
                                                                                                  "create-self-conversation"
                                                                                                  (Summary
                                                                                                     "Create a self-conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("self"
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "get-mls-self-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Get the user's MLS self-conversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("mls-self"
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[VersionedRespond
                                                                                                                                          'V5
                                                                                                                                          200
                                                                                                                                          "The MLS self-conversation"
                                                                                                                                          Conversation]
                                                                                                                                      Conversation)))))))
                                                                                                      :<|> (Named
                                                                                                              "get-mls-self-conversation"
                                                                                                              (Summary
                                                                                                                 "Get the user's MLS self-conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("mls-self"
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "The MLS self-conversation"
                                                                                                                                            Conversation]
                                                                                                                                        Conversation))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Get information about an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "get-sub-conversation"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSSubConvUnsupportedConvType
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("subconversations"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "subconv"
                                                                                                                                                               SubConvId
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'GET
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[Respond
                                                                                                                                                                      200
                                                                                                                                                                      "Subconversation"
                                                                                                                                                                      PublicSubConversation]
                                                                                                                                                                  PublicSubConversation)))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "leave-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Leave an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "leave-sub-conversation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSProtocolErrorTag
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSStaleMessage
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZClient
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("subconversations"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "subconv"
                                                                                                                                                                                     SubConvId
                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'DELETE
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "OK"]
                                                                                                                                                                                            ()))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "delete-subconversation"
                                                                                                                                (Summary
                                                                                                                                   "Delete an MLS subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "delete-sub-conversation"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSStaleMessage
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "subconv"
                                                                                                                                                                               SubConvId
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   DeleteSubConversationRequest
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'DELETE
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[Respond
                                                                                                                                                                                          200
                                                                                                                                                                                          "Deletion successful"
                                                                                                                                                                                          ()]
                                                                                                                                                                                      ())))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-subconversation-group-info"
                                                                                                                                      (Summary
                                                                                                                                         "Get MLS group information of subconversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "query-group-info"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSMissingGroupInfo
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("subconversations"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "subconv"
                                                                                                                                                                                 SubConvId
                                                                                                                                                                               :> ("groupinfo"
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[MLS]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "The group information"
                                                                                                                                                                                            GroupInfoData]
                                                                                                                                                                                        GroupInfoData))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-one-to-one-conversation@v2"
                                                                                                                                            (Summary
                                                                                                                                               "Create a 1:1 conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "api-version"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-created"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V3
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NonBindingTeam
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 200
                                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 201
                                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-one-to-one-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create a 1:1 conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-created"
                                                                                                                                                       :> (From
                                                                                                                                                             'V3
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NonBindingTeam
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         NewConv
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                   200
                                                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                                                Conversation
                                                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                   201
                                                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                                                               Conversation)))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation@v5"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V5
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V6
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "usr"
                                                                                                                                                                                               UserId
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'GET
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[VersionedRespond
                                                                                                                                                                                                      'V5
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                                      Conversation]
                                                                                                                                                                                                  Conversation))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation@v6"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V6
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V7
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                 UserId
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                           MLSPublicKey)]
                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                       MLSPublicKey))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-one-to-one-mls-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V7
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> (QueryParam
                                                                                                                                                                                                       "format"
                                                                                                                                                                                                       MLSPublicKeyFormat
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'GET
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                                 SomeKey)]
                                                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                                                             SomeKey))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add members to an existing conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             Invite
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation-unqualified2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (Until
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> ("v2"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "add-members-to-conversation"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (From
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'AddConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'LeaveConversation)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "join-conversation-by-id-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V5
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Join a conversation using a reusable code"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "code-check"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Check validity of a conversation code."
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> ("code-check"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationCode
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Valid"]
                                                                                                                                                                                                                                          ()))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V4
                                                                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                           'V4
                                                                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-code-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Delete conversation code"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                                                                                                                      Event]
                                                                                                                                                                                                                                                                  Event))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-code"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get existing conversation code"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "member-typing-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                                          ())))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "remove-member"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-other-member"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversation-ids-v2" (ListGlobalSelfConvs
-> QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConvIdsPage
forall p (r :: EffectRow).
(p ~ CassandraPaging,
 (Member ConversationStore r, Member (Error InternalError) r,
  Member (Input Env) r, Member (ListItems p ConvId) r,
  Member (ListItems p (Remote ConvId)) r,
  Member (Logger (Msg -> Msg)) r)) =>
ListGlobalSelfConvs
-> QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds
-> Sem r ConvIdsPage
conversationIdsPageFromV2 ListGlobalSelfConvs
DoNotListGlobalSelf)
    API
  (Named
     "list-conversation-ids-v2"
     (Summary "Get all conversation IDs."
      :> (Until 'V3
          :> (Description PaginationDocs
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("list-ids"
                          :> (ReqBody '[JSON] GetPaginatedConversationIds
                              :> Post '[JSON] ConvIdsPage))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversation-ids"
        (Summary "Get all conversation IDs."
         :> (From 'V3
             :> (Description PaginationDocs
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list-ids"
                             :> (ReqBody '[JSON] GetPaginatedConversationIds
                                 :> Post '[JSON] ConvIdsPage)))))))
      :<|> (Named
              "get-conversations"
              (Summary "Get all *local* conversations."
               :> (Until 'V3
                   :> (Description
                         "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                       :> (ZLocalUser
                           :> ("conversations"
                               :> (QueryParam'
                                     '[Optional, Strict,
                                       Description
                                         "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                     "ids"
                                     (Range 1 32 (CommaSeparatedList ConvId))
                                   :> (QueryParam'
                                         '[Optional, Strict,
                                           Description "Conversation ID to start from (exclusive)"]
                                         "start"
                                         ConvId
                                       :> (QueryParam'
                                             '[Optional, Strict,
                                               Description
                                                 "Maximum number of conversations to return"]
                                             "size"
                                             (Range 1 500 Int32)
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2
                                                    200
                                                    "List of local conversations"
                                                    (ConversationList Conversation)]
                                                (ConversationList Conversation)))))))))
            :<|> (Named
                    "list-conversations@v1"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (Until 'V2
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list"
                                         :> ("v2"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> Post '[JSON] ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations@v2"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V2
                                   :> (Until 'V3
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("list"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V2
                                                                200
                                                                "Conversation page"
                                                                ConversationsResponse]
                                                            ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations@v5"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V3
                                         :> (Until 'V6
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("list"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V5
                                                                      200
                                                                      "Conversation page"
                                                                      ConversationsResponse]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list"
                                                           :> (ReqBody '[JSON] ListConversations
                                                               :> Post
                                                                    '[JSON]
                                                                    ConversationsResponse)))))))
                                    :<|> (Named
                                            "get-conversation-by-reusable-code"
                                            (Summary
                                               "Get limited conversation information by key/code pair"
                                             :> (CanThrow 'CodeNotFound
                                                 :> (CanThrow 'InvalidConversationPassword
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("join"
                                                                                 :> (QueryParam'
                                                                                       '[Required,
                                                                                         Strict]
                                                                                       "key"
                                                                                       Key
                                                                                     :> (QueryParam'
                                                                                           '[Required,
                                                                                             Strict]
                                                                                           "code"
                                                                                           Value
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              ConversationCoverView))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v2"
                                                  (Summary "Create a new conversation"
                                                   :> (DescriptionOAuthScope 'WriteConversations
                                                       :> (MakesFederatedCall 'Brig "api-version"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (Until 'V3
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'MLSNonEmptyMemberList
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         UnreachableBackendsLegacy
                                                                                                       :> (Description
                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZOptConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (VersionedReqBody
                                                                                                                             'V2
                                                                                                                             '[JSON]
                                                                                                                             NewConv
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       200
                                                                                                                                       "Conversation existed"
                                                                                                                                       Conversation),
                                                                                                                                  WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       201
                                                                                                                                       "Conversation created"
                                                                                                                                       Conversation)]
                                                                                                                                (ResponseForExistedCreated
                                                                                                                                   Conversation))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v3"
                                                        (Summary "Create a new conversation"
                                                         :> (DescriptionOAuthScope
                                                               'WriteConversations
                                                             :> (MakesFederatedCall
                                                                   'Brig "api-version"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V3
                                                                             :> (Until 'V4
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSNonEmptyMemberList
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'MissingLegalholdConsent
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackendsLegacy
                                                                                                                 :> (Description
                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZOptConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       NewConv
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V3
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V3
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation)))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v5"
                                                              (Summary "Create a new conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Brig
                                                                         "get-not-fully-connected-backends"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V4
                                                                                   :> (Until 'V6
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSNonEmptyMemberList
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MissingLegalholdConsent
                                                                                                                   :> (CanThrow
                                                                                                                         NonFederatingBackends
                                                                                                                       :> (CanThrow
                                                                                                                             UnreachableBackends
                                                                                                                           :> (Description
                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 NewConv
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        CreateGroupConversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-not-fully-connected-backends"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V6
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'MLSNonEmptyMemberList
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (Description
                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZOptConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   NewConv
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          CreateGroupConversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation@v2"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (Until 'V3
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("self"
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V2
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V2
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation@v5"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (From 'V3
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("self"
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 Conversation)]
                                                                                                          (ResponseForExistedCreated
                                                                                                             Conversation)))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (From 'V6
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("self"
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation))))))
                                                                                    :<|> (Named
                                                                                            "get-mls-self-conversation@v5"
                                                                                            (Summary
                                                                                               "Get the user's MLS self-conversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> ("mls-self"
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[VersionedRespond
                                                                                                                              'V5
                                                                                                                              200
                                                                                                                              "The MLS self-conversation"
                                                                                                                              Conversation]
                                                                                                                          Conversation)))))))
                                                                                          :<|> (Named
                                                                                                  "get-mls-self-conversation"
                                                                                                  (Summary
                                                                                                     "Get the user's MLS self-conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("mls-self"
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "The MLS self-conversation"
                                                                                                                                Conversation]
                                                                                                                            Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "get-subconversation"
                                                                                                        (Summary
                                                                                                           "Get information about an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "get-sub-conversation"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSSubConvUnsupportedConvType
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("subconversations"
                                                                                                                                             :> (Capture
                                                                                                                                                   "subconv"
                                                                                                                                                   SubConvId
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'GET
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[Respond
                                                                                                                                                          200
                                                                                                                                                          "Subconversation"
                                                                                                                                                          PublicSubConversation]
                                                                                                                                                      PublicSubConversation)))))))))))
                                                                                                      :<|> (Named
                                                                                                              "leave-subconversation"
                                                                                                              (Summary
                                                                                                                 "Leave an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "leave-sub-conversation"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSProtocolErrorTag
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSStaleMessage
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZClient
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "subconv"
                                                                                                                                                                         SubConvId
                                                                                                                                                                       :> ("self"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'DELETE
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "OK"]
                                                                                                                                                                                ()))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "delete-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Delete an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "delete-sub-conversation"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSStaleMessage
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("subconversations"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "subconv"
                                                                                                                                                                   SubConvId
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       DeleteSubConversationRequest
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'DELETE
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[Respond
                                                                                                                                                                              200
                                                                                                                                                                              "Deletion successful"
                                                                                                                                                                              ()]
                                                                                                                                                                          ())))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-subconversation-group-info"
                                                                                                                          (Summary
                                                                                                                             "Get MLS group information of subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "query-group-info"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSMissingGroupInfo
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("subconversations"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "subconv"
                                                                                                                                                                     SubConvId
                                                                                                                                                                   :> ("groupinfo"
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[MLS]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "The group information"
                                                                                                                                                                                GroupInfoData]
                                                                                                                                                                            GroupInfoData))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-one-to-one-conversation@v2"
                                                                                                                                (Summary
                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "api-version"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-created"
                                                                                                                                         :> (Until
                                                                                                                                               'V3
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NonBindingTeam
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotConnected
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           OperationDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     200
                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     201
                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-one-to-one-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-created"
                                                                                                                                           :> (From
                                                                                                                                                 'V3
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             OperationDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                       200
                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                       201
                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (Until
                                                                                                                                                       'V6
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "usr"
                                                                                                                                                                                   UserId
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'GET
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[VersionedRespond
                                                                                                                                                                                          'V5
                                                                                                                                                                                          200
                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                          Conversation]
                                                                                                                                                                                      Conversation))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V6
                                                                                                                                                       :> (Until
                                                                                                                                                             'V7
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "usr"
                                                                                                                                                                                     UserId
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                               MLSPublicKey)]
                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                           MLSPublicKey))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V7
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotConnected
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> (QueryParam
                                                                                                                                                                                           "format"
                                                                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                     SomeKey)]
                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                 SomeKey))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 Invite
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (From
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V5
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "code-check"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationCode
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Valid"]
                                                                                                                                                                                                                              ()))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V4
                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V4
                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                                                                          Event]
                                                                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-code"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversation-ids-v2"
        (Summary "Get all conversation IDs."
         :> (Until 'V3
             :> (Description PaginationDocs
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list-ids"
                             :> (ReqBody '[JSON] GetPaginatedConversationIds
                                 :> Post '[JSON] ConvIdsPage)))))))
      :<|> (Named
              "list-conversation-ids"
              (Summary "Get all conversation IDs."
               :> (From 'V3
                   :> (Description PaginationDocs
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list-ids"
                                   :> (ReqBody '[JSON] GetPaginatedConversationIds
                                       :> Post '[JSON] ConvIdsPage)))))))
            :<|> (Named
                    "get-conversations"
                    (Summary "Get all *local* conversations."
                     :> (Until 'V3
                         :> (Description
                               "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QueryParam'
                                           '[Optional, Strict,
                                             Description
                                               "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                           "ids"
                                           (Range 1 32 (CommaSeparatedList ConvId))
                                         :> (QueryParam'
                                               '[Optional, Strict,
                                                 Description
                                                   "Conversation ID to start from (exclusive)"]
                                               "start"
                                               ConvId
                                             :> (QueryParam'
                                                   '[Optional, Strict,
                                                     Description
                                                       "Maximum number of conversations to return"]
                                                   "size"
                                                   (Range 1 500 Int32)
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V2
                                                          200
                                                          "List of local conversations"
                                                          (ConversationList Conversation)]
                                                      (ConversationList Conversation)))))))))
                  :<|> (Named
                          "list-conversations@v1"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (Until 'V2
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list"
                                               :> ("v2"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> Post '[JSON] ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations@v2"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V2
                                         :> (Until 'V3
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("list"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V2
                                                                      200
                                                                      "Conversation page"
                                                                      ConversationsResponse]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations@v5"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V3
                                               :> (Until 'V6
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("list"
                                                               :> (ReqBody '[JSON] ListConversations
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[VersionedRespond
                                                                            'V5
                                                                            200
                                                                            "Conversation page"
                                                                            ConversationsResponse]
                                                                        ConversationsResponse))))))))
                                    :<|> (Named
                                            "list-conversations"
                                            (Summary
                                               "Get conversation metadata for a list of conversation ids"
                                             :> (MakesFederatedCall 'Galley "get-conversations"
                                                 :> (From 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("list"
                                                                 :> (ReqBody
                                                                       '[JSON] ListConversations
                                                                     :> Post
                                                                          '[JSON]
                                                                          ConversationsResponse)))))))
                                          :<|> (Named
                                                  "get-conversation-by-reusable-code"
                                                  (Summary
                                                     "Get limited conversation information by key/code pair"
                                                   :> (CanThrow 'CodeNotFound
                                                       :> (CanThrow 'InvalidConversationPassword
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> ("join"
                                                                                       :> (QueryParam'
                                                                                             '[Required,
                                                                                               Strict]
                                                                                             "key"
                                                                                             Key
                                                                                           :> (QueryParam'
                                                                                                 '[Required,
                                                                                                   Strict]
                                                                                                 "code"
                                                                                                 Value
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    ConversationCoverView))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v2"
                                                        (Summary "Create a new conversation"
                                                         :> (DescriptionOAuthScope
                                                               'WriteConversations
                                                             :> (MakesFederatedCall
                                                                   'Brig "api-version"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (Until 'V3
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'MLSNonEmptyMemberList
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               UnreachableBackendsLegacy
                                                                                                             :> (Description
                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZOptConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (VersionedReqBody
                                                                                                                                   'V2
                                                                                                                                   '[JSON]
                                                                                                                                   NewConv
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             200
                                                                                                                                             "Conversation existed"
                                                                                                                                             Conversation),
                                                                                                                                        WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             201
                                                                                                                                             "Conversation created"
                                                                                                                                             Conversation)]
                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                         Conversation))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v3"
                                                              (Summary "Create a new conversation"
                                                               :> (DescriptionOAuthScope
                                                                     'WriteConversations
                                                                   :> (MakesFederatedCall
                                                                         'Brig "api-version"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V3
                                                                                   :> (Until 'V4
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSNonEmptyMemberList
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MissingLegalholdConsent
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackendsLegacy
                                                                                                                       :> (Description
                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZOptConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             NewConv
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V3
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V3
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       Conversation)]
                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                   Conversation)))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation@v5"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-not-fully-connected-backends"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V4
                                                                                         :> (Until
                                                                                               'V6
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSNonEmptyMemberList
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'MissingLegalholdConsent
                                                                                                                         :> (CanThrow
                                                                                                                               NonFederatingBackends
                                                                                                                             :> (CanThrow
                                                                                                                                   UnreachableBackends
                                                                                                                                 :> (Description
                                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       NewConv
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              CreateGroupConversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V5
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                                          CreateGroupConversationResponse)))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-group-conversation"
                                                                          (Summary
                                                                             "Create a new conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-not-fully-connected-backends"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-created"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (From
                                                                                                 'V6
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'MLSNonEmptyMemberList
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (Description
                                                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZOptConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         NewConv
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                Conversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   200
                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                   Conversation),
                                                                                                                                                              WithHeaders
                                                                                                                                                                ConversationHeaders
                                                                                                                                                                CreateGroupConversation
                                                                                                                                                                (VersionedRespond
                                                                                                                                                                   'V6
                                                                                                                                                                   201
                                                                                                                                                                   "Conversation created"
                                                                                                                                                                   CreateGroupConversation)]
                                                                                                                                                            CreateGroupConversationResponse))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation@v2"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (Until 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("self"
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V2
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V2
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation@v5"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (From 'V3
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("self"
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       Conversation)]
                                                                                                                (ResponseForExistedCreated
                                                                                                                   Conversation)))))))
                                                                                    :<|> (Named
                                                                                            "create-self-conversation"
                                                                                            (Summary
                                                                                               "Create a self-conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("self"
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "get-mls-self-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Get the user's MLS self-conversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> ("mls-self"
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[VersionedRespond
                                                                                                                                    'V5
                                                                                                                                    200
                                                                                                                                    "The MLS self-conversation"
                                                                                                                                    Conversation]
                                                                                                                                Conversation)))))))
                                                                                                :<|> (Named
                                                                                                        "get-mls-self-conversation"
                                                                                                        (Summary
                                                                                                           "Get the user's MLS self-conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("mls-self"
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "The MLS self-conversation"
                                                                                                                                      Conversation]
                                                                                                                                  Conversation))))))
                                                                                                      :<|> (Named
                                                                                                              "get-subconversation"
                                                                                                              (Summary
                                                                                                                 "Get information about an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "get-sub-conversation"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSSubConvUnsupportedConvType
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("subconversations"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "subconv"
                                                                                                                                                         SubConvId
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'GET
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[Respond
                                                                                                                                                                200
                                                                                                                                                                "Subconversation"
                                                                                                                                                                PublicSubConversation]
                                                                                                                                                            PublicSubConversation)))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "leave-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Leave an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "leave-sub-conversation"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSProtocolErrorTag
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSStaleMessage
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZClient
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("subconversations"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "subconv"
                                                                                                                                                                               SubConvId
                                                                                                                                                                             :> ("self"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'DELETE
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "OK"]
                                                                                                                                                                                      ()))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "delete-subconversation"
                                                                                                                          (Summary
                                                                                                                             "Delete an MLS subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "delete-sub-conversation"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSStaleMessage
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "subconv"
                                                                                                                                                                         SubConvId
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             DeleteSubConversationRequest
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'DELETE
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[Respond
                                                                                                                                                                                    200
                                                                                                                                                                                    "Deletion successful"
                                                                                                                                                                                    ()]
                                                                                                                                                                                ())))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-subconversation-group-info"
                                                                                                                                (Summary
                                                                                                                                   "Get MLS group information of subconversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "query-group-info"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSMissingGroupInfo
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("subconversations"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "subconv"
                                                                                                                                                                           SubConvId
                                                                                                                                                                         :> ("groupinfo"
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[MLS]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "The group information"
                                                                                                                                                                                      GroupInfoData]
                                                                                                                                                                                  GroupInfoData))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-one-to-one-conversation@v2"
                                                                                                                                      (Summary
                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "api-version"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-created"
                                                                                                                                               :> (Until
                                                                                                                                                     'V3
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NonBindingTeam
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotConnected
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 OperationDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 NewConv
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           200
                                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           201
                                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-one-to-one-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Create a 1:1 conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-created"
                                                                                                                                                 :> (From
                                                                                                                                                       'V3
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NonBindingTeam
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   NewConv
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                             200
                                                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                                                             Conversation),
                                                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                                                          Conversation
                                                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                             201
                                                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                                                         Conversation)))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation@v5"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V5
                                                                                                                                                       :> (Until
                                                                                                                                                             'V6
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSFederatedOne2OneNotSupported
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "usr"
                                                                                                                                                                                         UserId
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'GET
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[VersionedRespond
                                                                                                                                                                                                'V5
                                                                                                                                                                                                200
                                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                                Conversation]
                                                                                                                                                                                            Conversation))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation@v6"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V6
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V7
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                           "usr"
                                                                                                                                                                                           UserId
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                     MLSPublicKey)]
                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                 MLSPublicKey))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-one-to-one-mls-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V7
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MLSNotEnabled
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotConnected
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> (QueryParam
                                                                                                                                                                                                 "format"
                                                                                                                                                                                                 MLSPublicKeyFormat
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'GET
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                                           SomeKey)]
                                                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                                                       SomeKey))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add members to an existing conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       Invite
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation-unqualified2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (Until
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> ("v2"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "add-members-to-conversation"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (From
                                                                                                                                                                                               'V2
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'AddConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'LeaveConversation)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'NotConnected
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "join-conversation-by-id-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V5
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "join-conversation-by-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Join a conversation using a reusable code"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           JoinConversationByCode
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "code-check"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Check validity of a conversation code."
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> ("code-check"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationCode
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Valid"]
                                                                                                                                                                                                                                    ()))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V4
                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "create-conversation-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                     'V4
                                                                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-code-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Delete conversation code"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'DELETE
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                                                                                                                Event]
                                                                                                                                                                                                                                                            Event))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-code"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get existing conversation code"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "member-typing-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                                    ())))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "member-typing-qualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "remove-member"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-other-member"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversation-ids" ServerT
  (Summary "Get all conversation IDs."
   :> (From 'V3
       :> (Description PaginationDocs
           :> (ZLocalUser
               :> ("conversations"
                   :> ("list-ids"
                       :> (ReqBody '[JSON] GetPaginatedConversationIds
                           :> Post '[JSON] ConvIdsPage)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get all conversation IDs."
            :> (From 'V3
                :> (Description PaginationDocs
                    :> (ZLocalUser
                        :> ("conversations"
                            :> ("list-ids"
                                :> (ReqBody '[JSON] GetPaginatedConversationIds
                                    :> Post '[JSON] ConvIdsPage))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConvIdsPage
forall p (r :: EffectRow).
(p ~ CassandraPaging,
 (Member ConversationStore r, Member (Error InternalError) r,
  Member (Input Env) r, Member (ListItems p ConvId) r,
  Member (ListItems p (Remote ConvId)) r,
  Member (Logger (Msg -> Msg)) r)) =>
QualifiedWithTag 'QLocal UserId
-> GetPaginatedConversationIds -> Sem r ConvIdsPage
conversationIdsPageFrom
    API
  (Named
     "list-conversation-ids"
     (Summary "Get all conversation IDs."
      :> (From 'V3
          :> (Description PaginationDocs
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("list-ids"
                          :> (ReqBody '[JSON] GetPaginatedConversationIds
                              :> Post '[JSON] ConvIdsPage))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversations"
        (Summary "Get all *local* conversations."
         :> (Until 'V3
             :> (Description
                   "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                 :> (ZLocalUser
                     :> ("conversations"
                         :> (QueryParam'
                               '[Optional, Strict,
                                 Description
                                   "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                               "ids"
                               (Range 1 32 (CommaSeparatedList ConvId))
                             :> (QueryParam'
                                   '[Optional, Strict,
                                     Description "Conversation ID to start from (exclusive)"]
                                   "start"
                                   ConvId
                                 :> (QueryParam'
                                       '[Optional, Strict,
                                         Description "Maximum number of conversations to return"]
                                       "size"
                                       (Range 1 500 Int32)
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond
                                              'V2
                                              200
                                              "List of local conversations"
                                              (ConversationList Conversation)]
                                          (ConversationList Conversation)))))))))
      :<|> (Named
              "list-conversations@v1"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (Until 'V2
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list"
                                   :> ("v2"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> Post '[JSON] ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations@v2"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V2
                             :> (Until 'V3
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("list"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V2
                                                          200
                                                          "Conversation page"
                                                          ConversationsResponse]
                                                      ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations@v5"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V3
                                   :> (Until 'V6
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("list"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V5
                                                                200
                                                                "Conversation page"
                                                                ConversationsResponse]
                                                            ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list"
                                                     :> (ReqBody '[JSON] ListConversations
                                                         :> Post
                                                              '[JSON] ConversationsResponse)))))))
                              :<|> (Named
                                      "get-conversation-by-reusable-code"
                                      (Summary
                                         "Get limited conversation information by key/code pair"
                                       :> (CanThrow 'CodeNotFound
                                           :> (CanThrow 'InvalidConversationPassword
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("join"
                                                                           :> (QueryParam'
                                                                                 '[Required, Strict]
                                                                                 "key"
                                                                                 Key
                                                                               :> (QueryParam'
                                                                                     '[Required,
                                                                                       Strict]
                                                                                     "code"
                                                                                     Value
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        ConversationCoverView))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v2"
                                            (Summary "Create a new conversation"
                                             :> (DescriptionOAuthScope 'WriteConversations
                                                 :> (MakesFederatedCall 'Brig "api-version"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (Until 'V3
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow
                                                                           'MLSNonEmptyMemberList
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   UnreachableBackendsLegacy
                                                                                                 :> (Description
                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZOptConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (VersionedReqBody
                                                                                                                       'V2
                                                                                                                       '[JSON]
                                                                                                                       NewConv
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 200
                                                                                                                                 "Conversation existed"
                                                                                                                                 Conversation),
                                                                                                                            WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 201
                                                                                                                                 "Conversation created"
                                                                                                                                 Conversation)]
                                                                                                                          (ResponseForExistedCreated
                                                                                                                             Conversation))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v3"
                                                  (Summary "Create a new conversation"
                                                   :> (DescriptionOAuthScope 'WriteConversations
                                                       :> (MakesFederatedCall 'Brig "api-version"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V3
                                                                       :> (Until 'V4
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSNonEmptyMemberList
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'MissingLegalholdConsent
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackendsLegacy
                                                                                                           :> (Description
                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZOptConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 NewConv
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V3
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V3
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation)))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v5"
                                                        (Summary "Create a new conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Brig
                                                                   "get-not-fully-connected-backends"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V4
                                                                             :> (Until 'V6
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSNonEmptyMemberList
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'MissingLegalholdConsent
                                                                                                             :> (CanThrow
                                                                                                                   NonFederatingBackends
                                                                                                                 :> (CanThrow
                                                                                                                       UnreachableBackends
                                                                                                                     :> (Description
                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           NewConv
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  CreateGroupConversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation"
                                                              (Summary "Create a new conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Brig
                                                                         "get-not-fully-connected-backends"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V6
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'MLSNonEmptyMemberList
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (Description
                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZOptConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             NewConv
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    CreateGroupConversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                CreateGroupConversationResponse))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-self-conversation@v2"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (Until 'V3
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("self"
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V2
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V2
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation@v5"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (From 'V3
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("self"
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           Conversation)]
                                                                                                    (ResponseForExistedCreated
                                                                                                       Conversation)))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (From 'V6
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("self"
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation))))))
                                                                              :<|> (Named
                                                                                      "get-mls-self-conversation@v5"
                                                                                      (Summary
                                                                                         "Get the user's MLS self-conversation"
                                                                                       :> (From 'V5
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("mls-self"
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[VersionedRespond
                                                                                                                        'V5
                                                                                                                        200
                                                                                                                        "The MLS self-conversation"
                                                                                                                        Conversation]
                                                                                                                    Conversation)))))))
                                                                                    :<|> (Named
                                                                                            "get-mls-self-conversation"
                                                                                            (Summary
                                                                                               "Get the user's MLS self-conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("mls-self"
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "The MLS self-conversation"
                                                                                                                          Conversation]
                                                                                                                      Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "get-subconversation"
                                                                                                  (Summary
                                                                                                     "Get information about an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "get-sub-conversation"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSSubConvUnsupportedConvType
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("subconversations"
                                                                                                                                       :> (Capture
                                                                                                                                             "subconv"
                                                                                                                                             SubConvId
                                                                                                                                           :> MultiVerb
                                                                                                                                                'GET
                                                                                                                                                '[JSON]
                                                                                                                                                '[Respond
                                                                                                                                                    200
                                                                                                                                                    "Subconversation"
                                                                                                                                                    PublicSubConversation]
                                                                                                                                                PublicSubConversation)))))))))))
                                                                                                :<|> (Named
                                                                                                        "leave-subconversation"
                                                                                                        (Summary
                                                                                                           "Leave an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "leave-sub-conversation"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSProtocolErrorTag
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSStaleMessage
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZClient
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("subconversations"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "subconv"
                                                                                                                                                                   SubConvId
                                                                                                                                                                 :> ("self"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'DELETE
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "OK"]
                                                                                                                                                                          ()))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "delete-subconversation"
                                                                                                              (Summary
                                                                                                                 "Delete an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "delete-sub-conversation"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSStaleMessage
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("subconversations"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "subconv"
                                                                                                                                                             SubConvId
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 DeleteSubConversationRequest
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'DELETE
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[Respond
                                                                                                                                                                        200
                                                                                                                                                                        "Deletion successful"
                                                                                                                                                                        ()]
                                                                                                                                                                    ())))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-subconversation-group-info"
                                                                                                                    (Summary
                                                                                                                       "Get MLS group information of subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "query-group-info"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSMissingGroupInfo
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("subconversations"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "subconv"
                                                                                                                                                               SubConvId
                                                                                                                                                             :> ("groupinfo"
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[MLS]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "The group information"
                                                                                                                                                                          GroupInfoData]
                                                                                                                                                                      GroupInfoData))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-one-to-one-conversation@v2"
                                                                                                                          (Summary
                                                                                                                             "Create a 1:1 conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "api-version"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-created"
                                                                                                                                   :> (Until
                                                                                                                                         'V3
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NonBindingTeam
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotConnected
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     OperationDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               200
                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               201
                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                           Conversation))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-one-to-one-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-created"
                                                                                                                                     :> (From
                                                                                                                                           'V3
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NonBindingTeam
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                 200
                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                 201
                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                             Conversation)))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (Until
                                                                                                                                                 'V6
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "usr"
                                                                                                                                                                             UserId
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'GET
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[VersionedRespond
                                                                                                                                                                                    'V5
                                                                                                                                                                                    200
                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                    Conversation]
                                                                                                                                                                                Conversation))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V6
                                                                                                                                                 :> (Until
                                                                                                                                                       'V7
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "usr"
                                                                                                                                                                               UserId
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                         MLSPublicKey)]
                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                     MLSPublicKey))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V7
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotConnected
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> (QueryParam
                                                                                                                                                                                     "format"
                                                                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                               SomeKey)]
                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                           SomeKey))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           Invite
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (From
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "code-check"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> ("code-check"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationCode
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Valid"]
                                                                                                                                                                                                                        ()))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V4
                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V4
                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                                                                    Event]
                                                                                                                                                                                                                                                Event))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-code"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversation-ids"
        (Summary "Get all conversation IDs."
         :> (From 'V3
             :> (Description PaginationDocs
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list-ids"
                             :> (ReqBody '[JSON] GetPaginatedConversationIds
                                 :> Post '[JSON] ConvIdsPage)))))))
      :<|> (Named
              "get-conversations"
              (Summary "Get all *local* conversations."
               :> (Until 'V3
                   :> (Description
                         "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                       :> (ZLocalUser
                           :> ("conversations"
                               :> (QueryParam'
                                     '[Optional, Strict,
                                       Description
                                         "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                     "ids"
                                     (Range 1 32 (CommaSeparatedList ConvId))
                                   :> (QueryParam'
                                         '[Optional, Strict,
                                           Description "Conversation ID to start from (exclusive)"]
                                         "start"
                                         ConvId
                                       :> (QueryParam'
                                             '[Optional, Strict,
                                               Description
                                                 "Maximum number of conversations to return"]
                                             "size"
                                             (Range 1 500 Int32)
                                           :> MultiVerb
                                                'GET
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2
                                                    200
                                                    "List of local conversations"
                                                    (ConversationList Conversation)]
                                                (ConversationList Conversation)))))))))
            :<|> (Named
                    "list-conversations@v1"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (Until 'V2
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list"
                                         :> ("v2"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> Post '[JSON] ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations@v2"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V2
                                   :> (Until 'V3
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("list"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V2
                                                                200
                                                                "Conversation page"
                                                                ConversationsResponse]
                                                            ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations@v5"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V3
                                         :> (Until 'V6
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("list"
                                                         :> (ReqBody '[JSON] ListConversations
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[VersionedRespond
                                                                      'V5
                                                                      200
                                                                      "Conversation page"
                                                                      ConversationsResponse]
                                                                  ConversationsResponse))))))))
                              :<|> (Named
                                      "list-conversations"
                                      (Summary
                                         "Get conversation metadata for a list of conversation ids"
                                       :> (MakesFederatedCall 'Galley "get-conversations"
                                           :> (From 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("list"
                                                           :> (ReqBody '[JSON] ListConversations
                                                               :> Post
                                                                    '[JSON]
                                                                    ConversationsResponse)))))))
                                    :<|> (Named
                                            "get-conversation-by-reusable-code"
                                            (Summary
                                               "Get limited conversation information by key/code pair"
                                             :> (CanThrow 'CodeNotFound
                                                 :> (CanThrow 'InvalidConversationPassword
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> ("join"
                                                                                 :> (QueryParam'
                                                                                       '[Required,
                                                                                         Strict]
                                                                                       "key"
                                                                                       Key
                                                                                     :> (QueryParam'
                                                                                           '[Required,
                                                                                             Strict]
                                                                                           "code"
                                                                                           Value
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              ConversationCoverView))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v2"
                                                  (Summary "Create a new conversation"
                                                   :> (DescriptionOAuthScope 'WriteConversations
                                                       :> (MakesFederatedCall 'Brig "api-version"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (Until 'V3
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'MLSNonEmptyMemberList
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         UnreachableBackendsLegacy
                                                                                                       :> (Description
                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZOptConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (VersionedReqBody
                                                                                                                             'V2
                                                                                                                             '[JSON]
                                                                                                                             NewConv
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       200
                                                                                                                                       "Conversation existed"
                                                                                                                                       Conversation),
                                                                                                                                  WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       201
                                                                                                                                       "Conversation created"
                                                                                                                                       Conversation)]
                                                                                                                                (ResponseForExistedCreated
                                                                                                                                   Conversation))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v3"
                                                        (Summary "Create a new conversation"
                                                         :> (DescriptionOAuthScope
                                                               'WriteConversations
                                                             :> (MakesFederatedCall
                                                                   'Brig "api-version"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V3
                                                                             :> (Until 'V4
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSNonEmptyMemberList
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'MissingLegalholdConsent
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackendsLegacy
                                                                                                                 :> (Description
                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZOptConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       NewConv
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V3
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V3
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 Conversation)]
                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                             Conversation)))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation@v5"
                                                              (Summary "Create a new conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Brig
                                                                         "get-not-fully-connected-backends"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V4
                                                                                   :> (Until 'V6
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSNonEmptyMemberList
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'MissingLegalholdConsent
                                                                                                                   :> (CanThrow
                                                                                                                         NonFederatingBackends
                                                                                                                       :> (CanThrow
                                                                                                                             UnreachableBackends
                                                                                                                           :> (Description
                                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 NewConv
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        CreateGroupConversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V5
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           CreateGroupConversation)]
                                                                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-group-conversation"
                                                                    (Summary
                                                                       "Create a new conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-not-fully-connected-backends"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-created"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (From 'V6
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'MLSNonEmptyMemberList
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (Description
                                                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZOptConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   NewConv
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          Conversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             200
                                                                                                                                                             "Conversation existed"
                                                                                                                                                             Conversation),
                                                                                                                                                        WithHeaders
                                                                                                                                                          ConversationHeaders
                                                                                                                                                          CreateGroupConversation
                                                                                                                                                          (VersionedRespond
                                                                                                                                                             'V6
                                                                                                                                                             201
                                                                                                                                                             "Conversation created"
                                                                                                                                                             CreateGroupConversation)]
                                                                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation@v2"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (Until 'V3
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("self"
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V2
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V2
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation@v5"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (From 'V3
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("self"
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 Conversation)]
                                                                                                          (ResponseForExistedCreated
                                                                                                             Conversation)))))))
                                                                              :<|> (Named
                                                                                      "create-self-conversation"
                                                                                      (Summary
                                                                                         "Create a self-conversation"
                                                                                       :> (From 'V6
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("self"
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation))))))
                                                                                    :<|> (Named
                                                                                            "get-mls-self-conversation@v5"
                                                                                            (Summary
                                                                                               "Get the user's MLS self-conversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> ("mls-self"
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[VersionedRespond
                                                                                                                              'V5
                                                                                                                              200
                                                                                                                              "The MLS self-conversation"
                                                                                                                              Conversation]
                                                                                                                          Conversation)))))))
                                                                                          :<|> (Named
                                                                                                  "get-mls-self-conversation"
                                                                                                  (Summary
                                                                                                     "Get the user's MLS self-conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> ("mls-self"
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "The MLS self-conversation"
                                                                                                                                Conversation]
                                                                                                                            Conversation))))))
                                                                                                :<|> (Named
                                                                                                        "get-subconversation"
                                                                                                        (Summary
                                                                                                           "Get information about an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "get-sub-conversation"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSSubConvUnsupportedConvType
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("subconversations"
                                                                                                                                             :> (Capture
                                                                                                                                                   "subconv"
                                                                                                                                                   SubConvId
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'GET
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[Respond
                                                                                                                                                          200
                                                                                                                                                          "Subconversation"
                                                                                                                                                          PublicSubConversation]
                                                                                                                                                      PublicSubConversation)))))))))))
                                                                                                      :<|> (Named
                                                                                                              "leave-subconversation"
                                                                                                              (Summary
                                                                                                                 "Leave an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "leave-sub-conversation"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSProtocolErrorTag
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSStaleMessage
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZClient
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("subconversations"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "subconv"
                                                                                                                                                                         SubConvId
                                                                                                                                                                       :> ("self"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'DELETE
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "OK"]
                                                                                                                                                                                ()))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "delete-subconversation"
                                                                                                                    (Summary
                                                                                                                       "Delete an MLS subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "delete-sub-conversation"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSStaleMessage
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("subconversations"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "subconv"
                                                                                                                                                                   SubConvId
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       DeleteSubConversationRequest
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'DELETE
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[Respond
                                                                                                                                                                              200
                                                                                                                                                                              "Deletion successful"
                                                                                                                                                                              ()]
                                                                                                                                                                          ())))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-subconversation-group-info"
                                                                                                                          (Summary
                                                                                                                             "Get MLS group information of subconversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "query-group-info"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSMissingGroupInfo
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MLSNotEnabled
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("subconversations"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "subconv"
                                                                                                                                                                     SubConvId
                                                                                                                                                                   :> ("groupinfo"
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[MLS]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "The group information"
                                                                                                                                                                                GroupInfoData]
                                                                                                                                                                            GroupInfoData))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-one-to-one-conversation@v2"
                                                                                                                                (Summary
                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "api-version"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-created"
                                                                                                                                         :> (Until
                                                                                                                                               'V3
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NonBindingTeam
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotConnected
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           OperationDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                           'V2
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           NewConv
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     200
                                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     201
                                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-one-to-one-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Create a 1:1 conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-created"
                                                                                                                                           :> (From
                                                                                                                                                 'V3
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NoBindingTeamMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NonBindingTeam
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             OperationDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             NewConv
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                       200
                                                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                                                       Conversation),
                                                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                                                    Conversation
                                                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                       201
                                                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V5
                                                                                                                                                 :> (Until
                                                                                                                                                       'V6
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "usr"
                                                                                                                                                                                   UserId
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'GET
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[VersionedRespond
                                                                                                                                                                                          'V5
                                                                                                                                                                                          200
                                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                                          Conversation]
                                                                                                                                                                                      Conversation))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V6
                                                                                                                                                       :> (Until
                                                                                                                                                             'V7
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                     "usr"
                                                                                                                                                                                     UserId
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                               MLSPublicKey)]
                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                           MLSPublicKey))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                                                                         :> (From
                                                                                                                                                               'V7
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MLSNotEnabled
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotConnected
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> (QueryParam
                                                                                                                                                                                           "format"
                                                                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'GET
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                                     SomeKey)]
                                                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                                                 SomeKey))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 Invite
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (Until
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "add-members-to-conversation"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (From
                                                                                                                                                                                         'V2
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'AddConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'LeaveConversation)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'NotConnected
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V5
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "code-check"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationCode
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Valid"]
                                                                                                                                                                                                                              ()))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V4
                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V4
                                                                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                                                                          Event]
                                                                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-code"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversations" ServerT
  (Summary "Get all *local* conversations."
   :> (Until 'V3
       :> (Description
             "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
           :> (ZLocalUser
               :> ("conversations"
                   :> (QueryParam'
                         '[Optional, Strict,
                           Description
                             "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                         "ids"
                         (Range 1 32 (CommaSeparatedList ConvId))
                       :> (QueryParam'
                             '[Optional, Strict,
                               Description "Conversation ID to start from (exclusive)"]
                             "start"
                             ConvId
                           :> (QueryParam'
                                 '[Optional, Strict,
                                   Description "Maximum number of conversations to return"]
                                 "size"
                                 (Range 1 500 Int32)
                               :> MultiVerb
                                    'GET
                                    '[JSON]
                                    '[VersionedRespond
                                        'V2
                                        200
                                        "List of local conversations"
                                        (ConversationList Conversation)]
                                    (ConversationList Conversation)))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get all *local* conversations."
            :> (Until 'V3
                :> (Description
                      "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                    :> (ZLocalUser
                        :> ("conversations"
                            :> (QueryParam'
                                  '[Optional, Strict,
                                    Description
                                      "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                                  "ids"
                                  (Range 1 32 (CommaSeparatedList ConvId))
                                :> (QueryParam'
                                      '[Optional, Strict,
                                        Description "Conversation ID to start from (exclusive)"]
                                      "start"
                                      ConvId
                                    :> (QueryParam'
                                          '[Optional, Strict,
                                            Description "Maximum number of conversations to return"]
                                          "size"
                                          (Range 1 500 Int32)
                                        :> MultiVerb
                                             'GET
                                             '[JSON]
                                             '[VersionedRespond
                                                 'V2
                                                 200
                                                 "List of local conversations"
                                                 (ConversationList Conversation)]
                                             (ConversationList Conversation))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Maybe (Range 1 32 (CommaSeparatedList ConvId))
-> Maybe ConvId
-> Maybe (Range 1 500 Int32)
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationList Conversation)
forall (r :: EffectRow).
(Member (Error InternalError) r,
 Member (ListItems LegacyPaging ConvId) r,
 Member ConversationStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe (Range 1 32 (CommaSeparatedList ConvId))
-> Maybe ConvId
-> Maybe (Range 1 500 Int32)
-> Sem r (ConversationList Conversation)
getConversations
    API
  (Named
     "get-conversations"
     (Summary "Get all *local* conversations."
      :> (Until 'V3
          :> (Description
                "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
              :> (ZLocalUser
                  :> ("conversations"
                      :> (QueryParam'
                            '[Optional, Strict,
                              Description
                                "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                            "ids"
                            (Range 1 32 (CommaSeparatedList ConvId))
                          :> (QueryParam'
                                '[Optional, Strict,
                                  Description "Conversation ID to start from (exclusive)"]
                                "start"
                                ConvId
                              :> (QueryParam'
                                    '[Optional, Strict,
                                      Description "Maximum number of conversations to return"]
                                    "size"
                                    (Range 1 500 Int32)
                                  :> MultiVerb
                                       'GET
                                       '[JSON]
                                       '[VersionedRespond
                                           'V2
                                           200
                                           "List of local conversations"
                                           (ConversationList Conversation)]
                                       (ConversationList Conversation))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversations@v1"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (Until 'V2
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list"
                             :> ("v2"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> Post '[JSON] ConversationsResponse))))))))
      :<|> (Named
              "list-conversations@v2"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V2
                       :> (Until 'V3
                           :> (ZLocalUser
                               :> ("conversations"
                                   :> ("list"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2
                                                    200
                                                    "Conversation page"
                                                    ConversationsResponse]
                                                ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations@v5"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V3
                             :> (Until 'V6
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("list"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V5
                                                          200
                                                          "Conversation page"
                                                          ConversationsResponse]
                                                      ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list"
                                               :> (ReqBody '[JSON] ListConversations
                                                   :> Post '[JSON] ConversationsResponse)))))))
                        :<|> (Named
                                "get-conversation-by-reusable-code"
                                (Summary "Get limited conversation information by key/code pair"
                                 :> (CanThrow 'CodeNotFound
                                     :> (CanThrow 'InvalidConversationPassword
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("join"
                                                                     :> (QueryParam'
                                                                           '[Required, Strict]
                                                                           "key"
                                                                           Key
                                                                         :> (QueryParam'
                                                                               '[Required, Strict]
                                                                               "code"
                                                                               Value
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  ConversationCoverView))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v2"
                                      (Summary "Create a new conversation"
                                       :> (DescriptionOAuthScope 'WriteConversations
                                           :> (MakesFederatedCall 'Brig "api-version"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (Until 'V3
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'MLSNonEmptyMemberList
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             UnreachableBackendsLegacy
                                                                                           :> (Description
                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZOptConn
                                                                                                       :> ("conversations"
                                                                                                           :> (VersionedReqBody
                                                                                                                 'V2
                                                                                                                 '[JSON]
                                                                                                                 NewConv
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           200
                                                                                                                           "Conversation existed"
                                                                                                                           Conversation),
                                                                                                                      WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           201
                                                                                                                           "Conversation created"
                                                                                                                           Conversation)]
                                                                                                                    (ResponseForExistedCreated
                                                                                                                       Conversation))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v3"
                                            (Summary "Create a new conversation"
                                             :> (DescriptionOAuthScope 'WriteConversations
                                                 :> (MakesFederatedCall 'Brig "api-version"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V3
                                                                 :> (Until 'V4
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSNonEmptyMemberList
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'MissingLegalholdConsent
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackendsLegacy
                                                                                                     :> (Description
                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZOptConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           NewConv
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V3
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V3
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation)))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v5"
                                                  (Summary "Create a new conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Brig
                                                             "get-not-fully-connected-backends"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V4
                                                                       :> (Until 'V6
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSNonEmptyMemberList
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'MissingLegalholdConsent
                                                                                                       :> (CanThrow
                                                                                                             NonFederatingBackends
                                                                                                           :> (CanThrow
                                                                                                                 UnreachableBackends
                                                                                                               :> (Description
                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     NewConv
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            CreateGroupConversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               CreateGroupConversation)]
                                                                                                                                        CreateGroupConversationResponse)))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation"
                                                        (Summary "Create a new conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Brig
                                                                   "get-not-fully-connected-backends"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V6
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'MLSNonEmptyMemberList
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (Description
                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZOptConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       NewConv
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              CreateGroupConversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                          CreateGroupConversationResponse))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-self-conversation@v2"
                                                              (Summary "Create a self-conversation"
                                                               :> (Until 'V3
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("self"
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V2
                                                                                           200
                                                                                           "Conversation existed"
                                                                                           Conversation),
                                                                                      WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V2
                                                                                           201
                                                                                           "Conversation created"
                                                                                           Conversation)]
                                                                                    (ResponseForExistedCreated
                                                                                       Conversation))))))
                                                            :<|> (Named
                                                                    "create-self-conversation@v5"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (From 'V3
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("self"
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     Conversation)]
                                                                                              (ResponseForExistedCreated
                                                                                                 Conversation)))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (From 'V6
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("self"
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation))))))
                                                                        :<|> (Named
                                                                                "get-mls-self-conversation@v5"
                                                                                (Summary
                                                                                   "Get the user's MLS self-conversation"
                                                                                 :> (From 'V5
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("mls-self"
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[VersionedRespond
                                                                                                                  'V5
                                                                                                                  200
                                                                                                                  "The MLS self-conversation"
                                                                                                                  Conversation]
                                                                                                              Conversation)))))))
                                                                              :<|> (Named
                                                                                      "get-mls-self-conversation"
                                                                                      (Summary
                                                                                         "Get the user's MLS self-conversation"
                                                                                       :> (From 'V6
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("mls-self"
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "The MLS self-conversation"
                                                                                                                    Conversation]
                                                                                                                Conversation))))))
                                                                                    :<|> (Named
                                                                                            "get-subconversation"
                                                                                            (Summary
                                                                                               "Get information about an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "get-sub-conversation"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSSubConvUnsupportedConvType
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("subconversations"
                                                                                                                                 :> (Capture
                                                                                                                                       "subconv"
                                                                                                                                       SubConvId
                                                                                                                                     :> MultiVerb
                                                                                                                                          'GET
                                                                                                                                          '[JSON]
                                                                                                                                          '[Respond
                                                                                                                                              200
                                                                                                                                              "Subconversation"
                                                                                                                                              PublicSubConversation]
                                                                                                                                          PublicSubConversation)))))))))))
                                                                                          :<|> (Named
                                                                                                  "leave-subconversation"
                                                                                                  (Summary
                                                                                                     "Leave an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "leave-sub-conversation"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSProtocolErrorTag
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSStaleMessage
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZClient
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("subconversations"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "subconv"
                                                                                                                                                             SubConvId
                                                                                                                                                           :> ("self"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'DELETE
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "OK"]
                                                                                                                                                                    ()))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "delete-subconversation"
                                                                                                        (Summary
                                                                                                           "Delete an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "delete-sub-conversation"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSStaleMessage
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("subconversations"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "subconv"
                                                                                                                                                       SubConvId
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           DeleteSubConversationRequest
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'DELETE
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[Respond
                                                                                                                                                                  200
                                                                                                                                                                  "Deletion successful"
                                                                                                                                                                  ()]
                                                                                                                                                              ())))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-subconversation-group-info"
                                                                                                              (Summary
                                                                                                                 "Get MLS group information of subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "query-group-info"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSMissingGroupInfo
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("subconversations"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "subconv"
                                                                                                                                                         SubConvId
                                                                                                                                                       :> ("groupinfo"
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[MLS]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "The group information"
                                                                                                                                                                    GroupInfoData]
                                                                                                                                                                GroupInfoData))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-one-to-one-conversation@v2"
                                                                                                                    (Summary
                                                                                                                       "Create a 1:1 conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "api-version"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-created"
                                                                                                                             :> (Until
                                                                                                                                   'V3
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NonBindingTeam
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotConnected
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                               'V2
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               NewConv
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         200
                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         201
                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                     Conversation))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-one-to-one-conversation"
                                                                                                                          (Summary
                                                                                                                             "Create a 1:1 conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-created"
                                                                                                                               :> (From
                                                                                                                                     'V3
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NonBindingTeam
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 NewConv
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V3
                                                                                                                                                                                                           200
                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V3
                                                                                                                                                                                                           201
                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                       Conversation)))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("one2one"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "usr"
                                                                                                                                                                       UserId
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                              'V5
                                                                                                                                                                              200
                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                              Conversation]
                                                                                                                                                                          Conversation))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (Until
                                                                                                                                                 'V7
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("one2one"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "usr"
                                                                                                                                                                         UserId
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                   MLSPublicKey)]
                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                               MLSPublicKey))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V7
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotConnected
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> (QueryParam
                                                                                                                                                                               "format"
                                                                                                                                                                               MLSPublicKeyFormat
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                         SomeKey)]
                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                     SomeKey))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     Invite
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (From
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "code-check"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> ("code-check"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationCode
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Valid"]
                                                                                                                                                                                                                  ()))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V4
                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V4
                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Delete conversation code"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                                                                              Event]
                                                                                                                                                                                                                                          Event))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-code"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversations"
        (Summary "Get all *local* conversations."
         :> (Until 'V3
             :> (Description
                   "Will not return remote conversations.\n\nUse `POST /conversations/list-ids` followed by `POST /conversations/list` instead."
                 :> (ZLocalUser
                     :> ("conversations"
                         :> (QueryParam'
                               '[Optional, Strict,
                                 Description
                                   "Mutually exclusive with 'start' (at most 32 IDs per request)"]
                               "ids"
                               (Range 1 32 (CommaSeparatedList ConvId))
                             :> (QueryParam'
                                   '[Optional, Strict,
                                     Description "Conversation ID to start from (exclusive)"]
                                   "start"
                                   ConvId
                                 :> (QueryParam'
                                       '[Optional, Strict,
                                         Description "Maximum number of conversations to return"]
                                       "size"
                                       (Range 1 500 Int32)
                                     :> MultiVerb
                                          'GET
                                          '[JSON]
                                          '[VersionedRespond
                                              'V2
                                              200
                                              "List of local conversations"
                                              (ConversationList Conversation)]
                                          (ConversationList Conversation)))))))))
      :<|> (Named
              "list-conversations@v1"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (Until 'V2
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list"
                                   :> ("v2"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> Post '[JSON] ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations@v2"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V2
                             :> (Until 'V3
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("list"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V2
                                                          200
                                                          "Conversation page"
                                                          ConversationsResponse]
                                                      ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations@v5"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V3
                                   :> (Until 'V6
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("list"
                                                   :> (ReqBody '[JSON] ListConversations
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[VersionedRespond
                                                                'V5
                                                                200
                                                                "Conversation page"
                                                                ConversationsResponse]
                                                            ConversationsResponse))))))))
                        :<|> (Named
                                "list-conversations"
                                (Summary "Get conversation metadata for a list of conversation ids"
                                 :> (MakesFederatedCall 'Galley "get-conversations"
                                     :> (From 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("list"
                                                     :> (ReqBody '[JSON] ListConversations
                                                         :> Post
                                                              '[JSON] ConversationsResponse)))))))
                              :<|> (Named
                                      "get-conversation-by-reusable-code"
                                      (Summary
                                         "Get limited conversation information by key/code pair"
                                       :> (CanThrow 'CodeNotFound
                                           :> (CanThrow 'InvalidConversationPassword
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> ("join"
                                                                           :> (QueryParam'
                                                                                 '[Required, Strict]
                                                                                 "key"
                                                                                 Key
                                                                               :> (QueryParam'
                                                                                     '[Required,
                                                                                       Strict]
                                                                                     "code"
                                                                                     Value
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        ConversationCoverView))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v2"
                                            (Summary "Create a new conversation"
                                             :> (DescriptionOAuthScope 'WriteConversations
                                                 :> (MakesFederatedCall 'Brig "api-version"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (Until 'V3
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow
                                                                           'MLSNonEmptyMemberList
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   UnreachableBackendsLegacy
                                                                                                 :> (Description
                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZOptConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (VersionedReqBody
                                                                                                                       'V2
                                                                                                                       '[JSON]
                                                                                                                       NewConv
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 200
                                                                                                                                 "Conversation existed"
                                                                                                                                 Conversation),
                                                                                                                            WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 201
                                                                                                                                 "Conversation created"
                                                                                                                                 Conversation)]
                                                                                                                          (ResponseForExistedCreated
                                                                                                                             Conversation))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v3"
                                                  (Summary "Create a new conversation"
                                                   :> (DescriptionOAuthScope 'WriteConversations
                                                       :> (MakesFederatedCall 'Brig "api-version"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V3
                                                                       :> (Until 'V4
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSNonEmptyMemberList
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'MissingLegalholdConsent
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackendsLegacy
                                                                                                           :> (Description
                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZOptConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 NewConv
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V3
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V3
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           Conversation)]
                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                       Conversation)))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation@v5"
                                                        (Summary "Create a new conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Brig
                                                                   "get-not-fully-connected-backends"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V4
                                                                             :> (Until 'V6
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSNonEmptyMemberList
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'MissingLegalholdConsent
                                                                                                             :> (CanThrow
                                                                                                                   NonFederatingBackends
                                                                                                                 :> (CanThrow
                                                                                                                       UnreachableBackends
                                                                                                                     :> (Description
                                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           NewConv
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  CreateGroupConversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V5
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     CreateGroupConversation)]
                                                                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-group-conversation"
                                                              (Summary "Create a new conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Brig
                                                                         "get-not-fully-connected-backends"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-created"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (From 'V6
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'MLSNonEmptyMemberList
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (Description
                                                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZOptConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             NewConv
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    Conversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       200
                                                                                                                                                       "Conversation existed"
                                                                                                                                                       Conversation),
                                                                                                                                                  WithHeaders
                                                                                                                                                    ConversationHeaders
                                                                                                                                                    CreateGroupConversation
                                                                                                                                                    (VersionedRespond
                                                                                                                                                       'V6
                                                                                                                                                       201
                                                                                                                                                       "Conversation created"
                                                                                                                                                       CreateGroupConversation)]
                                                                                                                                                CreateGroupConversationResponse))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-self-conversation@v2"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (Until 'V3
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("self"
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V2
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V2
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation@v5"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (From 'V3
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("self"
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           Conversation)]
                                                                                                    (ResponseForExistedCreated
                                                                                                       Conversation)))))))
                                                                        :<|> (Named
                                                                                "create-self-conversation"
                                                                                (Summary
                                                                                   "Create a self-conversation"
                                                                                 :> (From 'V6
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("self"
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation))))))
                                                                              :<|> (Named
                                                                                      "get-mls-self-conversation@v5"
                                                                                      (Summary
                                                                                         "Get the user's MLS self-conversation"
                                                                                       :> (From 'V5
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> ("mls-self"
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[VersionedRespond
                                                                                                                        'V5
                                                                                                                        200
                                                                                                                        "The MLS self-conversation"
                                                                                                                        Conversation]
                                                                                                                    Conversation)))))))
                                                                                    :<|> (Named
                                                                                            "get-mls-self-conversation"
                                                                                            (Summary
                                                                                               "Get the user's MLS self-conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> ("mls-self"
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "The MLS self-conversation"
                                                                                                                          Conversation]
                                                                                                                      Conversation))))))
                                                                                          :<|> (Named
                                                                                                  "get-subconversation"
                                                                                                  (Summary
                                                                                                     "Get information about an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "get-sub-conversation"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSSubConvUnsupportedConvType
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("subconversations"
                                                                                                                                       :> (Capture
                                                                                                                                             "subconv"
                                                                                                                                             SubConvId
                                                                                                                                           :> MultiVerb
                                                                                                                                                'GET
                                                                                                                                                '[JSON]
                                                                                                                                                '[Respond
                                                                                                                                                    200
                                                                                                                                                    "Subconversation"
                                                                                                                                                    PublicSubConversation]
                                                                                                                                                PublicSubConversation)))))))))))
                                                                                                :<|> (Named
                                                                                                        "leave-subconversation"
                                                                                                        (Summary
                                                                                                           "Leave an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "leave-sub-conversation"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSProtocolErrorTag
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSStaleMessage
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZClient
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("subconversations"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "subconv"
                                                                                                                                                                   SubConvId
                                                                                                                                                                 :> ("self"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'DELETE
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "OK"]
                                                                                                                                                                          ()))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "delete-subconversation"
                                                                                                              (Summary
                                                                                                                 "Delete an MLS subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "delete-sub-conversation"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSStaleMessage
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("subconversations"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "subconv"
                                                                                                                                                             SubConvId
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 DeleteSubConversationRequest
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'DELETE
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[Respond
                                                                                                                                                                        200
                                                                                                                                                                        "Deletion successful"
                                                                                                                                                                        ()]
                                                                                                                                                                    ())))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-subconversation-group-info"
                                                                                                                    (Summary
                                                                                                                       "Get MLS group information of subconversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "query-group-info"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSMissingGroupInfo
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MLSNotEnabled
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("subconversations"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "subconv"
                                                                                                                                                               SubConvId
                                                                                                                                                             :> ("groupinfo"
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[MLS]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "The group information"
                                                                                                                                                                          GroupInfoData]
                                                                                                                                                                      GroupInfoData))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-one-to-one-conversation@v2"
                                                                                                                          (Summary
                                                                                                                             "Create a 1:1 conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "api-version"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-created"
                                                                                                                                   :> (Until
                                                                                                                                         'V3
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NonBindingTeam
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotConnected
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     OperationDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                     'V2
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     NewConv
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               200
                                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                                               Conversation),
                                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                                            Conversation
                                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               201
                                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                                           Conversation))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-one-to-one-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Create a 1:1 conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-created"
                                                                                                                                     :> (From
                                                                                                                                           'V3
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NoBindingTeamMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NonBindingTeam
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> ("one2one"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       NewConv
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                 200
                                                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                                                 Conversation),
                                                                                                                                                                                                            WithHeaders
                                                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                                                              Conversation
                                                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                 201
                                                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                                                 Conversation)]
                                                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                                                             Conversation)))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V5
                                                                                                                                           :> (Until
                                                                                                                                                 'V6
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "usr"
                                                                                                                                                                             UserId
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'GET
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[VersionedRespond
                                                                                                                                                                                    'V5
                                                                                                                                                                                    200
                                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                                    Conversation]
                                                                                                                                                                                Conversation))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V6
                                                                                                                                                 :> (Until
                                                                                                                                                       'V7
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'MLSNotEnabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                               "usr"
                                                                                                                                                                               UserId
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                         MLSPublicKey)]
                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                     MLSPublicKey))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                                                                   :> (From
                                                                                                                                                         'V7
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MLSNotEnabled
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotConnected
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> (QueryParam
                                                                                                                                                                                     "format"
                                                                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'GET
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[Respond
                                                                                                                                                                                            200
                                                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                                               SomeKey)]
                                                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                                                           SomeKey))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           Invite
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (Until
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "add-members-to-conversation"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (From
                                                                                                                                                                                   'V2
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'AddConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'LeaveConversation)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'NotConnected
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V5
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "code-check"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> ("code-check"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationCode
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Valid"]
                                                                                                                                                                                                                        ()))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V4
                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V4
                                                                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("features"
                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                                                                    Event]
                                                                                                                                                                                                                                                Event))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-code"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'GET
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversations@v1" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ListConversations -> Sem r ConversationsResponse
listConversations))
    API
  (Named
     "list-conversations@v1"
     (Summary "Get conversation metadata for a list of conversation ids"
      :> (MakesFederatedCall 'Galley "get-conversations"
          :> (Until 'V2
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("list"
                          :> ("v2"
                              :> (ReqBody '[JSON] ListConversations
                                  :> Post '[JSON] ConversationsResponse)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversations@v2"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V2
                 :> (Until 'V3
                     :> (ZLocalUser
                         :> ("conversations"
                             :> ("list"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[VersionedRespond
                                              'V2 200 "Conversation page" ConversationsResponse]
                                          ConversationsResponse))))))))
      :<|> (Named
              "list-conversations@v5"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V3
                       :> (Until 'V6
                           :> (ZLocalUser
                               :> ("conversations"
                                   :> ("list"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V5
                                                    200
                                                    "Conversation page"
                                                    ConversationsResponse]
                                                ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list"
                                         :> (ReqBody '[JSON] ListConversations
                                             :> Post '[JSON] ConversationsResponse)))))))
                  :<|> (Named
                          "get-conversation-by-reusable-code"
                          (Summary "Get limited conversation information by key/code pair"
                           :> (CanThrow 'CodeNotFound
                               :> (CanThrow 'InvalidConversationPassword
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'NotATeamMember
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("join"
                                                               :> (QueryParam'
                                                                     '[Required, Strict] "key" Key
                                                                   :> (QueryParam'
                                                                         '[Required, Strict]
                                                                         "code"
                                                                         Value
                                                                       :> Get
                                                                            '[JSON]
                                                                            ConversationCoverView))))))))))))
                        :<|> (Named
                                "create-group-conversation@v2"
                                (Summary "Create a new conversation"
                                 :> (DescriptionOAuthScope 'WriteConversations
                                     :> (MakesFederatedCall 'Brig "api-version"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (Until 'V3
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'MLSNonEmptyMemberList
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       UnreachableBackendsLegacy
                                                                                     :> (Description
                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZOptConn
                                                                                                 :> ("conversations"
                                                                                                     :> (VersionedReqBody
                                                                                                           'V2
                                                                                                           '[JSON]
                                                                                                           NewConv
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     200
                                                                                                                     "Conversation existed"
                                                                                                                     Conversation),
                                                                                                                WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     201
                                                                                                                     "Conversation created"
                                                                                                                     Conversation)]
                                                                                                              (ResponseForExistedCreated
                                                                                                                 Conversation))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v3"
                                      (Summary "Create a new conversation"
                                       :> (DescriptionOAuthScope 'WriteConversations
                                           :> (MakesFederatedCall 'Brig "api-version"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V3
                                                           :> (Until 'V4
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSNonEmptyMemberList
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'MissingLegalholdConsent
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackendsLegacy
                                                                                               :> (Description
                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZOptConn
                                                                                                           :> ("conversations"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     NewConv
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V3
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V3
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation)))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v5"
                                            (Summary "Create a new conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Brig "get-not-fully-connected-backends"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V4
                                                                 :> (Until 'V6
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSNonEmptyMemberList
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'MissingLegalholdConsent
                                                                                                 :> (CanThrow
                                                                                                       NonFederatingBackends
                                                                                                     :> (CanThrow
                                                                                                           UnreachableBackends
                                                                                                         :> (Description
                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               NewConv
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      CreateGroupConversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         CreateGroupConversation)]
                                                                                                                                  CreateGroupConversationResponse)))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation"
                                                  (Summary "Create a new conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Brig
                                                             "get-not-fully-connected-backends"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V6
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'MLSNonEmptyMemberList
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (Description
                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZOptConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 NewConv
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        CreateGroupConversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           CreateGroupConversation)]
                                                                                                                                    CreateGroupConversationResponse))))))))))))))))))))
                                                :<|> (Named
                                                        "create-self-conversation@v2"
                                                        (Summary "Create a self-conversation"
                                                         :> (Until 'V3
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("self"
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V2
                                                                                     200
                                                                                     "Conversation existed"
                                                                                     Conversation),
                                                                                WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V2
                                                                                     201
                                                                                     "Conversation created"
                                                                                     Conversation)]
                                                                              (ResponseForExistedCreated
                                                                                 Conversation))))))
                                                      :<|> (Named
                                                              "create-self-conversation@v5"
                                                              (Summary "Create a self-conversation"
                                                               :> (From 'V3
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("self"
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V5
                                                                                               200
                                                                                               "Conversation existed"
                                                                                               Conversation),
                                                                                          WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V5
                                                                                               201
                                                                                               "Conversation created"
                                                                                               Conversation)]
                                                                                        (ResponseForExistedCreated
                                                                                           Conversation)))))))
                                                            :<|> (Named
                                                                    "create-self-conversation"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (From 'V6
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("self"
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation))))))
                                                                  :<|> (Named
                                                                          "get-mls-self-conversation@v5"
                                                                          (Summary
                                                                             "Get the user's MLS self-conversation"
                                                                           :> (From 'V5
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("mls-self"
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[VersionedRespond
                                                                                                            'V5
                                                                                                            200
                                                                                                            "The MLS self-conversation"
                                                                                                            Conversation]
                                                                                                        Conversation)))))))
                                                                        :<|> (Named
                                                                                "get-mls-self-conversation"
                                                                                (Summary
                                                                                   "Get the user's MLS self-conversation"
                                                                                 :> (From 'V6
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("mls-self"
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "The MLS self-conversation"
                                                                                                              Conversation]
                                                                                                          Conversation))))))
                                                                              :<|> (Named
                                                                                      "get-subconversation"
                                                                                      (Summary
                                                                                         "Get information about an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "get-sub-conversation"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSSubConvUnsupportedConvType
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("subconversations"
                                                                                                                           :> (Capture
                                                                                                                                 "subconv"
                                                                                                                                 SubConvId
                                                                                                                               :> MultiVerb
                                                                                                                                    'GET
                                                                                                                                    '[JSON]
                                                                                                                                    '[Respond
                                                                                                                                        200
                                                                                                                                        "Subconversation"
                                                                                                                                        PublicSubConversation]
                                                                                                                                    PublicSubConversation)))))))))))
                                                                                    :<|> (Named
                                                                                            "leave-subconversation"
                                                                                            (Summary
                                                                                               "Leave an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "leave-sub-conversation"
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSProtocolErrorTag
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSStaleMessage
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZClient
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("subconversations"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "subconv"
                                                                                                                                                       SubConvId
                                                                                                                                                     :> ("self"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'DELETE
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "OK"]
                                                                                                                                                              ()))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "delete-subconversation"
                                                                                                  (Summary
                                                                                                     "Delete an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "delete-sub-conversation"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSStaleMessage
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("subconversations"
                                                                                                                                           :> (Capture
                                                                                                                                                 "subconv"
                                                                                                                                                 SubConvId
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     DeleteSubConversationRequest
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'DELETE
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[Respond
                                                                                                                                                            200
                                                                                                                                                            "Deletion successful"
                                                                                                                                                            ()]
                                                                                                                                                        ())))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-subconversation-group-info"
                                                                                                        (Summary
                                                                                                           "Get MLS group information of subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "query-group-info"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSMissingGroupInfo
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("subconversations"
                                                                                                                                             :> (Capture
                                                                                                                                                   "subconv"
                                                                                                                                                   SubConvId
                                                                                                                                                 :> ("groupinfo"
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[MLS]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "The group information"
                                                                                                                                                              GroupInfoData]
                                                                                                                                                          GroupInfoData))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-one-to-one-conversation@v2"
                                                                                                              (Summary
                                                                                                                 "Create a 1:1 conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-created"
                                                                                                                       :> (Until
                                                                                                                             'V3
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NonBindingTeam
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotConnected
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TeamNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                         'V2
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         NewConv
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                Conversation
                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   200
                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                Conversation
                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   201
                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                               Conversation))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-one-to-one-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a 1:1 conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-created"
                                                                                                                         :> (From
                                                                                                                               'V3
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NonBindingTeam
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TeamNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           NewConv
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V3
                                                                                                                                                                                                     200
                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V3
                                                                                                                                                                                                     201
                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                 Conversation)))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNotEnabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("one2one"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "usr"
                                                                                                                                                                 UserId
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                        'V5
                                                                                                                                                                        200
                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                        Conversation]
                                                                                                                                                                    Conversation))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (Until
                                                                                                                                           'V7
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("one2one"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "usr"
                                                                                                                                                                   UserId
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                             MLSPublicKey)]
                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                         MLSPublicKey))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V7
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotConnected
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> ("one2one"
                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> (QueryParam
                                                                                                                                                                         "format"
                                                                                                                                                                         MLSPublicKeyFormat
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                   SomeKey)]
                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                               SomeKey))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               Invite
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (From
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "code-check"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Check validity of a conversation code."
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> ("code-check"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationCode
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'POST
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Valid"]
                                                                                                                                                                                                            ()))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V4
                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V4
                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Delete conversation code"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                                                                        Event]
                                                                                                                                                                                                                                    Event))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-code"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-member"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversations@v1"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (Until 'V2
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list"
                             :> ("v2"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> Post '[JSON] ConversationsResponse))))))))
      :<|> (Named
              "list-conversations@v2"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V2
                       :> (Until 'V3
                           :> (ZLocalUser
                               :> ("conversations"
                                   :> ("list"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V2
                                                    200
                                                    "Conversation page"
                                                    ConversationsResponse]
                                                ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations@v5"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V3
                             :> (Until 'V6
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("list"
                                             :> (ReqBody '[JSON] ListConversations
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[VersionedRespond
                                                          'V5
                                                          200
                                                          "Conversation page"
                                                          ConversationsResponse]
                                                      ConversationsResponse))))))))
                  :<|> (Named
                          "list-conversations"
                          (Summary "Get conversation metadata for a list of conversation ids"
                           :> (MakesFederatedCall 'Galley "get-conversations"
                               :> (From 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("list"
                                               :> (ReqBody '[JSON] ListConversations
                                                   :> Post '[JSON] ConversationsResponse)))))))
                        :<|> (Named
                                "get-conversation-by-reusable-code"
                                (Summary "Get limited conversation information by key/code pair"
                                 :> (CanThrow 'CodeNotFound
                                     :> (CanThrow 'InvalidConversationPassword
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> ("join"
                                                                     :> (QueryParam'
                                                                           '[Required, Strict]
                                                                           "key"
                                                                           Key
                                                                         :> (QueryParam'
                                                                               '[Required, Strict]
                                                                               "code"
                                                                               Value
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  ConversationCoverView))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v2"
                                      (Summary "Create a new conversation"
                                       :> (DescriptionOAuthScope 'WriteConversations
                                           :> (MakesFederatedCall 'Brig "api-version"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (Until 'V3
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'MLSNonEmptyMemberList
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             UnreachableBackendsLegacy
                                                                                           :> (Description
                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZOptConn
                                                                                                       :> ("conversations"
                                                                                                           :> (VersionedReqBody
                                                                                                                 'V2
                                                                                                                 '[JSON]
                                                                                                                 NewConv
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           200
                                                                                                                           "Conversation existed"
                                                                                                                           Conversation),
                                                                                                                      WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           201
                                                                                                                           "Conversation created"
                                                                                                                           Conversation)]
                                                                                                                    (ResponseForExistedCreated
                                                                                                                       Conversation))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v3"
                                            (Summary "Create a new conversation"
                                             :> (DescriptionOAuthScope 'WriteConversations
                                                 :> (MakesFederatedCall 'Brig "api-version"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V3
                                                                 :> (Until 'V4
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSNonEmptyMemberList
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'MissingLegalholdConsent
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackendsLegacy
                                                                                                     :> (Description
                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZOptConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           NewConv
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V3
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V3
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     Conversation)]
                                                                                                                              (ResponseForExistedCreated
                                                                                                                                 Conversation)))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation@v5"
                                                  (Summary "Create a new conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Brig
                                                             "get-not-fully-connected-backends"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V4
                                                                       :> (Until 'V6
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSNonEmptyMemberList
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'MissingLegalholdConsent
                                                                                                       :> (CanThrow
                                                                                                             NonFederatingBackends
                                                                                                           :> (CanThrow
                                                                                                                 UnreachableBackends
                                                                                                               :> (Description
                                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     NewConv
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            CreateGroupConversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V5
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               CreateGroupConversation)]
                                                                                                                                        CreateGroupConversationResponse)))))))))))))))))))))
                                                :<|> (Named
                                                        "create-group-conversation"
                                                        (Summary "Create a new conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Brig
                                                                   "get-not-fully-connected-backends"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-created"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (From 'V6
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'MLSNonEmptyMemberList
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (Description
                                                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZOptConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       NewConv
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              Conversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 200
                                                                                                                                                 "Conversation existed"
                                                                                                                                                 Conversation),
                                                                                                                                            WithHeaders
                                                                                                                                              ConversationHeaders
                                                                                                                                              CreateGroupConversation
                                                                                                                                              (VersionedRespond
                                                                                                                                                 'V6
                                                                                                                                                 201
                                                                                                                                                 "Conversation created"
                                                                                                                                                 CreateGroupConversation)]
                                                                                                                                          CreateGroupConversationResponse))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-self-conversation@v2"
                                                              (Summary "Create a self-conversation"
                                                               :> (Until 'V3
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("self"
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V2
                                                                                           200
                                                                                           "Conversation existed"
                                                                                           Conversation),
                                                                                      WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V2
                                                                                           201
                                                                                           "Conversation created"
                                                                                           Conversation)]
                                                                                    (ResponseForExistedCreated
                                                                                       Conversation))))))
                                                            :<|> (Named
                                                                    "create-self-conversation@v5"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (From 'V3
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("self"
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     Conversation)]
                                                                                              (ResponseForExistedCreated
                                                                                                 Conversation)))))))
                                                                  :<|> (Named
                                                                          "create-self-conversation"
                                                                          (Summary
                                                                             "Create a self-conversation"
                                                                           :> (From 'V6
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("self"
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation))))))
                                                                        :<|> (Named
                                                                                "get-mls-self-conversation@v5"
                                                                                (Summary
                                                                                   "Get the user's MLS self-conversation"
                                                                                 :> (From 'V5
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> ("mls-self"
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[VersionedRespond
                                                                                                                  'V5
                                                                                                                  200
                                                                                                                  "The MLS self-conversation"
                                                                                                                  Conversation]
                                                                                                              Conversation)))))))
                                                                              :<|> (Named
                                                                                      "get-mls-self-conversation"
                                                                                      (Summary
                                                                                         "Get the user's MLS self-conversation"
                                                                                       :> (From 'V6
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> ("mls-self"
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "The MLS self-conversation"
                                                                                                                    Conversation]
                                                                                                                Conversation))))))
                                                                                    :<|> (Named
                                                                                            "get-subconversation"
                                                                                            (Summary
                                                                                               "Get information about an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "get-sub-conversation"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'MLSSubConvUnsupportedConvType
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("subconversations"
                                                                                                                                 :> (Capture
                                                                                                                                       "subconv"
                                                                                                                                       SubConvId
                                                                                                                                     :> MultiVerb
                                                                                                                                          'GET
                                                                                                                                          '[JSON]
                                                                                                                                          '[Respond
                                                                                                                                              200
                                                                                                                                              "Subconversation"
                                                                                                                                              PublicSubConversation]
                                                                                                                                          PublicSubConversation)))))))))))
                                                                                          :<|> (Named
                                                                                                  "leave-subconversation"
                                                                                                  (Summary
                                                                                                     "Leave an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "leave-sub-conversation"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSProtocolErrorTag
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSStaleMessage
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZClient
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("subconversations"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "subconv"
                                                                                                                                                             SubConvId
                                                                                                                                                           :> ("self"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'DELETE
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "OK"]
                                                                                                                                                                    ()))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "delete-subconversation"
                                                                                                        (Summary
                                                                                                           "Delete an MLS subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "delete-sub-conversation"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSStaleMessage
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("subconversations"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "subconv"
                                                                                                                                                       SubConvId
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           DeleteSubConversationRequest
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'DELETE
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[Respond
                                                                                                                                                                  200
                                                                                                                                                                  "Deletion successful"
                                                                                                                                                                  ()]
                                                                                                                                                              ())))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-subconversation-group-info"
                                                                                                              (Summary
                                                                                                                 "Get MLS group information of subconversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "query-group-info"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSMissingGroupInfo
                                                                                                                               :> (CanThrow
                                                                                                                                     'MLSNotEnabled
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("subconversations"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "subconv"
                                                                                                                                                         SubConvId
                                                                                                                                                       :> ("groupinfo"
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[MLS]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "The group information"
                                                                                                                                                                    GroupInfoData]
                                                                                                                                                                GroupInfoData))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-one-to-one-conversation@v2"
                                                                                                                    (Summary
                                                                                                                       "Create a 1:1 conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "api-version"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-created"
                                                                                                                             :> (Until
                                                                                                                                   'V3
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NoBindingTeamMembers
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NonBindingTeam
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotConnected
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                               'V2
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               NewConv
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         200
                                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                                         Conversation),
                                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                                      Conversation
                                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         201
                                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                                     Conversation))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-one-to-one-conversation"
                                                                                                                          (Summary
                                                                                                                             "Create a 1:1 conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-created"
                                                                                                                               :> (From
                                                                                                                                     'V3
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NoBindingTeamMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NonBindingTeam
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> ("one2one"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 NewConv
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V3
                                                                                                                                                                                                           200
                                                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                                                           Conversation),
                                                                                                                                                                                                      WithHeaders
                                                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                                                        Conversation
                                                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                                                           'V3
                                                                                                                                                                                                           201
                                                                                                                                                                                                           "Conversation created"
                                                                                                                                                                                                           Conversation)]
                                                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                                                       Conversation)))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V5
                                                                                                                                     :> (Until
                                                                                                                                           'V6
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("one2one"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "usr"
                                                                                                                                                                       UserId
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[VersionedRespond
                                                                                                                                                                              'V5
                                                                                                                                                                              200
                                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                                              Conversation]
                                                                                                                                                                          Conversation))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V6
                                                                                                                                           :> (Until
                                                                                                                                                 'V7
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'MLSNotEnabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("one2one"
                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                         "usr"
                                                                                                                                                                         UserId
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                   MLSPublicKey)]
                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                               MLSPublicKey))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-one-to-one-mls-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Get an MLS 1:1 conversation"
                                                                                                                                             :> (From
                                                                                                                                                   'V7
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MLSNotEnabled
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotConnected
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> (QueryParam
                                                                                                                                                                               "format"
                                                                                                                                                                               MLSPublicKeyFormat
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'GET
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[Respond
                                                                                                                                                                                      200
                                                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                                         SomeKey)]
                                                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                                                     SomeKey))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     Invite
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (Until
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "add-members-to-conversation"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (From
                                                                                                                                                                             'V2
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'AddConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'LeaveConversation)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'NotConnected
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V5
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "code-check"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> ("code-check"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationCode
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Valid"]
                                                                                                                                                                                                                  ()))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V4
                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V4
                                                                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Delete conversation code"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'DELETE
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                                                                              Event]
                                                                                                                                                                                                                                          Event))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-code"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'GET
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversations@v2" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ListConversations -> Sem r ConversationsResponse
listConversations))
    API
  (Named
     "list-conversations@v2"
     (Summary "Get conversation metadata for a list of conversation ids"
      :> (MakesFederatedCall 'Galley "get-conversations"
          :> (From 'V2
              :> (Until 'V3
                  :> (ZLocalUser
                      :> ("conversations"
                          :> ("list"
                              :> (ReqBody '[JSON] ListConversations
                                  :> MultiVerb
                                       'POST
                                       '[JSON]
                                       '[VersionedRespond
                                           'V2 200 "Conversation page" ConversationsResponse]
                                       ConversationsResponse)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversations@v5"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V3
                 :> (Until 'V6
                     :> (ZLocalUser
                         :> ("conversations"
                             :> ("list"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[VersionedRespond
                                              'V5 200 "Conversation page" ConversationsResponse]
                                          ConversationsResponse))))))))
      :<|> (Named
              "list-conversations"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list"
                                   :> (ReqBody '[JSON] ListConversations
                                       :> Post '[JSON] ConversationsResponse)))))))
            :<|> (Named
                    "get-conversation-by-reusable-code"
                    (Summary "Get limited conversation information by key/code pair"
                     :> (CanThrow 'CodeNotFound
                         :> (CanThrow 'InvalidConversationPassword
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'NotATeamMember
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("join"
                                                         :> (QueryParam'
                                                               '[Required, Strict] "key" Key
                                                             :> (QueryParam'
                                                                   '[Required, Strict] "code" Value
                                                                 :> Get
                                                                      '[JSON]
                                                                      ConversationCoverView))))))))))))
                  :<|> (Named
                          "create-group-conversation@v2"
                          (Summary "Create a new conversation"
                           :> (DescriptionOAuthScope 'WriteConversations
                               :> (MakesFederatedCall 'Brig "api-version"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (Until 'V3
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'MLSNonEmptyMemberList
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 UnreachableBackendsLegacy
                                                                               :> (Description
                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZOptConn
                                                                                           :> ("conversations"
                                                                                               :> (VersionedReqBody
                                                                                                     'V2
                                                                                                     '[JSON]
                                                                                                     NewConv
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               200
                                                                                                               "Conversation existed"
                                                                                                               Conversation),
                                                                                                          WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               201
                                                                                                               "Conversation created"
                                                                                                               Conversation)]
                                                                                                        (ResponseForExistedCreated
                                                                                                           Conversation))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation@v3"
                                (Summary "Create a new conversation"
                                 :> (DescriptionOAuthScope 'WriteConversations
                                     :> (MakesFederatedCall 'Brig "api-version"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V3
                                                     :> (Until 'V4
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'MissingLegalholdConsent
                                                                                     :> (CanThrow
                                                                                           UnreachableBackendsLegacy
                                                                                         :> (Description
                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZOptConn
                                                                                                     :> ("conversations"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               NewConv
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V3
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V3
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation)))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v5"
                                      (Summary "Create a new conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall
                                                 'Brig "get-not-fully-connected-backends"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V4
                                                           :> (Until 'V6
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSNonEmptyMemberList
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'MissingLegalholdConsent
                                                                                           :> (CanThrow
                                                                                                 NonFederatingBackends
                                                                                               :> (CanThrow
                                                                                                     UnreachableBackends
                                                                                                   :> (Description
                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         NewConv
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                CreateGroupConversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   CreateGroupConversation)]
                                                                                                                            CreateGroupConversationResponse)))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation"
                                            (Summary "Create a new conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Brig "get-not-fully-connected-backends"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V6
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow
                                                                           'MLSNonEmptyMemberList
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (Description
                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZOptConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           NewConv
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  CreateGroupConversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     CreateGroupConversation)]
                                                                                                                              CreateGroupConversationResponse))))))))))))))))))))
                                          :<|> (Named
                                                  "create-self-conversation@v2"
                                                  (Summary "Create a self-conversation"
                                                   :> (Until 'V3
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("self"
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V2
                                                                               200
                                                                               "Conversation existed"
                                                                               Conversation),
                                                                          WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V2
                                                                               201
                                                                               "Conversation created"
                                                                               Conversation)]
                                                                        (ResponseForExistedCreated
                                                                           Conversation))))))
                                                :<|> (Named
                                                        "create-self-conversation@v5"
                                                        (Summary "Create a self-conversation"
                                                         :> (From 'V3
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("self"
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V5
                                                                                         200
                                                                                         "Conversation existed"
                                                                                         Conversation),
                                                                                    WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V5
                                                                                         201
                                                                                         "Conversation created"
                                                                                         Conversation)]
                                                                                  (ResponseForExistedCreated
                                                                                     Conversation)))))))
                                                      :<|> (Named
                                                              "create-self-conversation"
                                                              (Summary "Create a self-conversation"
                                                               :> (From 'V6
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("self"
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V6
                                                                                           200
                                                                                           "Conversation existed"
                                                                                           Conversation),
                                                                                      WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V6
                                                                                           201
                                                                                           "Conversation created"
                                                                                           Conversation)]
                                                                                    (ResponseForExistedCreated
                                                                                       Conversation))))))
                                                            :<|> (Named
                                                                    "get-mls-self-conversation@v5"
                                                                    (Summary
                                                                       "Get the user's MLS self-conversation"
                                                                     :> (From 'V5
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("mls-self"
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[VersionedRespond
                                                                                                      'V5
                                                                                                      200
                                                                                                      "The MLS self-conversation"
                                                                                                      Conversation]
                                                                                                  Conversation)))))))
                                                                  :<|> (Named
                                                                          "get-mls-self-conversation"
                                                                          (Summary
                                                                             "Get the user's MLS self-conversation"
                                                                           :> (From 'V6
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("mls-self"
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "The MLS self-conversation"
                                                                                                        Conversation]
                                                                                                    Conversation))))))
                                                                        :<|> (Named
                                                                                "get-subconversation"
                                                                                (Summary
                                                                                   "Get information about an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "get-sub-conversation"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSSubConvUnsupportedConvType
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("subconversations"
                                                                                                                     :> (Capture
                                                                                                                           "subconv"
                                                                                                                           SubConvId
                                                                                                                         :> MultiVerb
                                                                                                                              'GET
                                                                                                                              '[JSON]
                                                                                                                              '[Respond
                                                                                                                                  200
                                                                                                                                  "Subconversation"
                                                                                                                                  PublicSubConversation]
                                                                                                                              PublicSubConversation)))))))))))
                                                                              :<|> (Named
                                                                                      "leave-subconversation"
                                                                                      (Summary
                                                                                         "Leave an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "leave-sub-conversation"
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MLSProtocolErrorTag
                                                                                                               :> (CanThrow
                                                                                                                     'MLSStaleMessage
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZClient
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("subconversations"
                                                                                                                                           :> (Capture
                                                                                                                                                 "subconv"
                                                                                                                                                 SubConvId
                                                                                                                                               :> ("self"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'DELETE
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "OK"]
                                                                                                                                                        ()))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "delete-subconversation"
                                                                                            (Summary
                                                                                               "Delete an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "delete-sub-conversation"
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSStaleMessage
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("subconversations"
                                                                                                                                     :> (Capture
                                                                                                                                           "subconv"
                                                                                                                                           SubConvId
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               DeleteSubConversationRequest
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'DELETE
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[Respond
                                                                                                                                                      200
                                                                                                                                                      "Deletion successful"
                                                                                                                                                      ()]
                                                                                                                                                  ())))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-subconversation-group-info"
                                                                                                  (Summary
                                                                                                     "Get MLS group information of subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "query-group-info"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'MLSMissingGroupInfo
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("subconversations"
                                                                                                                                       :> (Capture
                                                                                                                                             "subconv"
                                                                                                                                             SubConvId
                                                                                                                                           :> ("groupinfo"
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[MLS]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "The group information"
                                                                                                                                                        GroupInfoData]
                                                                                                                                                    GroupInfoData))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-one-to-one-conversation@v2"
                                                                                                        (Summary
                                                                                                           "Create a 1:1 conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-created"
                                                                                                                 :> (Until
                                                                                                                       'V3
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NonBindingTeam
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotConnected
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TeamNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                   'V2
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   NewConv
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             200
                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                             Conversation),
                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             201
                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                         Conversation))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-one-to-one-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a 1:1 conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-created"
                                                                                                                   :> (From
                                                                                                                         'V3
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NonBindingTeam
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     NewConv
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V3
                                                                                                                                                                                               200
                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                               Conversation),
                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V3
                                                                                                                                                                                               201
                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                           Conversation)))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNotEnabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("one2one"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "usr"
                                                                                                                                                           UserId
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                  'V5
                                                                                                                                                                  200
                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                  Conversation]
                                                                                                                                                              Conversation))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation@v6"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (Until
                                                                                                                                     'V7
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNotEnabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("one2one"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "usr"
                                                                                                                                                             UserId
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                       MLSPublicKey)]
                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                   MLSPublicKey))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V7
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> ("one2one"
                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> (QueryParam
                                                                                                                                                                   "format"
                                                                                                                                                                   MLSPublicKeyFormat
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                             SomeKey)]
                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                         SomeKey))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (Until
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         Invite
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation-unqualified2"
                                                                                                                                            (Summary
                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> ("v2"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (From
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Join a conversation using a reusable code"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "code-check"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Check validity of a conversation code."
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> ("code-check"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationCode
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Valid"]
                                                                                                                                                                                                      ()))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V4
                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V4
                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Delete conversation code"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                                                                  Event]
                                                                                                                                                                                                                              Event))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-code"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-member"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversations@v2"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V2
                 :> (Until 'V3
                     :> (ZLocalUser
                         :> ("conversations"
                             :> ("list"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[VersionedRespond
                                              'V2 200 "Conversation page" ConversationsResponse]
                                          ConversationsResponse))))))))
      :<|> (Named
              "list-conversations@v5"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V3
                       :> (Until 'V6
                           :> (ZLocalUser
                               :> ("conversations"
                                   :> ("list"
                                       :> (ReqBody '[JSON] ListConversations
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[VersionedRespond
                                                    'V5
                                                    200
                                                    "Conversation page"
                                                    ConversationsResponse]
                                                ConversationsResponse))))))))
            :<|> (Named
                    "list-conversations"
                    (Summary "Get conversation metadata for a list of conversation ids"
                     :> (MakesFederatedCall 'Galley "get-conversations"
                         :> (From 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("list"
                                         :> (ReqBody '[JSON] ListConversations
                                             :> Post '[JSON] ConversationsResponse)))))))
                  :<|> (Named
                          "get-conversation-by-reusable-code"
                          (Summary "Get limited conversation information by key/code pair"
                           :> (CanThrow 'CodeNotFound
                               :> (CanThrow 'InvalidConversationPassword
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'NotATeamMember
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> ("join"
                                                               :> (QueryParam'
                                                                     '[Required, Strict] "key" Key
                                                                   :> (QueryParam'
                                                                         '[Required, Strict]
                                                                         "code"
                                                                         Value
                                                                       :> Get
                                                                            '[JSON]
                                                                            ConversationCoverView))))))))))))
                        :<|> (Named
                                "create-group-conversation@v2"
                                (Summary "Create a new conversation"
                                 :> (DescriptionOAuthScope 'WriteConversations
                                     :> (MakesFederatedCall 'Brig "api-version"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (Until 'V3
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'MLSNonEmptyMemberList
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       UnreachableBackendsLegacy
                                                                                     :> (Description
                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZOptConn
                                                                                                 :> ("conversations"
                                                                                                     :> (VersionedReqBody
                                                                                                           'V2
                                                                                                           '[JSON]
                                                                                                           NewConv
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     200
                                                                                                                     "Conversation existed"
                                                                                                                     Conversation),
                                                                                                                WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     201
                                                                                                                     "Conversation created"
                                                                                                                     Conversation)]
                                                                                                              (ResponseForExistedCreated
                                                                                                                 Conversation))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v3"
                                      (Summary "Create a new conversation"
                                       :> (DescriptionOAuthScope 'WriteConversations
                                           :> (MakesFederatedCall 'Brig "api-version"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V3
                                                           :> (Until 'V4
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSNonEmptyMemberList
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'MissingLegalholdConsent
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackendsLegacy
                                                                                               :> (Description
                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZOptConn
                                                                                                           :> ("conversations"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     NewConv
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V3
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V3
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               Conversation)]
                                                                                                                        (ResponseForExistedCreated
                                                                                                                           Conversation)))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation@v5"
                                            (Summary "Create a new conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Brig "get-not-fully-connected-backends"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V4
                                                                 :> (Until 'V6
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSNonEmptyMemberList
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'MissingLegalholdConsent
                                                                                                 :> (CanThrow
                                                                                                       NonFederatingBackends
                                                                                                     :> (CanThrow
                                                                                                           UnreachableBackends
                                                                                                         :> (Description
                                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               NewConv
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      CreateGroupConversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V5
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         CreateGroupConversation)]
                                                                                                                                  CreateGroupConversationResponse)))))))))))))))))))))
                                          :<|> (Named
                                                  "create-group-conversation"
                                                  (Summary "Create a new conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Brig
                                                             "get-not-fully-connected-backends"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-created"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (From 'V6
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'MLSNonEmptyMemberList
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (Description
                                                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZOptConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 NewConv
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        Conversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           200
                                                                                                                                           "Conversation existed"
                                                                                                                                           Conversation),
                                                                                                                                      WithHeaders
                                                                                                                                        ConversationHeaders
                                                                                                                                        CreateGroupConversation
                                                                                                                                        (VersionedRespond
                                                                                                                                           'V6
                                                                                                                                           201
                                                                                                                                           "Conversation created"
                                                                                                                                           CreateGroupConversation)]
                                                                                                                                    CreateGroupConversationResponse))))))))))))))))))))
                                                :<|> (Named
                                                        "create-self-conversation@v2"
                                                        (Summary "Create a self-conversation"
                                                         :> (Until 'V3
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("self"
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V2
                                                                                     200
                                                                                     "Conversation existed"
                                                                                     Conversation),
                                                                                WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V2
                                                                                     201
                                                                                     "Conversation created"
                                                                                     Conversation)]
                                                                              (ResponseForExistedCreated
                                                                                 Conversation))))))
                                                      :<|> (Named
                                                              "create-self-conversation@v5"
                                                              (Summary "Create a self-conversation"
                                                               :> (From 'V3
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("self"
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V5
                                                                                               200
                                                                                               "Conversation existed"
                                                                                               Conversation),
                                                                                          WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V5
                                                                                               201
                                                                                               "Conversation created"
                                                                                               Conversation)]
                                                                                        (ResponseForExistedCreated
                                                                                           Conversation)))))))
                                                            :<|> (Named
                                                                    "create-self-conversation"
                                                                    (Summary
                                                                       "Create a self-conversation"
                                                                     :> (From 'V6
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("self"
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation))))))
                                                                  :<|> (Named
                                                                          "get-mls-self-conversation@v5"
                                                                          (Summary
                                                                             "Get the user's MLS self-conversation"
                                                                           :> (From 'V5
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> ("mls-self"
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[VersionedRespond
                                                                                                            'V5
                                                                                                            200
                                                                                                            "The MLS self-conversation"
                                                                                                            Conversation]
                                                                                                        Conversation)))))))
                                                                        :<|> (Named
                                                                                "get-mls-self-conversation"
                                                                                (Summary
                                                                                   "Get the user's MLS self-conversation"
                                                                                 :> (From 'V6
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> ("mls-self"
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "The MLS self-conversation"
                                                                                                              Conversation]
                                                                                                          Conversation))))))
                                                                              :<|> (Named
                                                                                      "get-subconversation"
                                                                                      (Summary
                                                                                         "Get information about an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "get-sub-conversation"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'MLSSubConvUnsupportedConvType
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("subconversations"
                                                                                                                           :> (Capture
                                                                                                                                 "subconv"
                                                                                                                                 SubConvId
                                                                                                                               :> MultiVerb
                                                                                                                                    'GET
                                                                                                                                    '[JSON]
                                                                                                                                    '[Respond
                                                                                                                                        200
                                                                                                                                        "Subconversation"
                                                                                                                                        PublicSubConversation]
                                                                                                                                    PublicSubConversation)))))))))))
                                                                                    :<|> (Named
                                                                                            "leave-subconversation"
                                                                                            (Summary
                                                                                               "Leave an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "leave-sub-conversation"
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSProtocolErrorTag
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSStaleMessage
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZClient
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("subconversations"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "subconv"
                                                                                                                                                       SubConvId
                                                                                                                                                     :> ("self"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'DELETE
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "OK"]
                                                                                                                                                              ()))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "delete-subconversation"
                                                                                                  (Summary
                                                                                                     "Delete an MLS subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "delete-sub-conversation"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSStaleMessage
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("subconversations"
                                                                                                                                           :> (Capture
                                                                                                                                                 "subconv"
                                                                                                                                                 SubConvId
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     DeleteSubConversationRequest
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'DELETE
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[Respond
                                                                                                                                                            200
                                                                                                                                                            "Deletion successful"
                                                                                                                                                            ()]
                                                                                                                                                        ())))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-subconversation-group-info"
                                                                                                        (Summary
                                                                                                           "Get MLS group information of subconversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "query-group-info"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSMissingGroupInfo
                                                                                                                         :> (CanThrow
                                                                                                                               'MLSNotEnabled
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("subconversations"
                                                                                                                                             :> (Capture
                                                                                                                                                   "subconv"
                                                                                                                                                   SubConvId
                                                                                                                                                 :> ("groupinfo"
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[MLS]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "The group information"
                                                                                                                                                              GroupInfoData]
                                                                                                                                                          GroupInfoData))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-one-to-one-conversation@v2"
                                                                                                              (Summary
                                                                                                                 "Create a 1:1 conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "api-version"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-created"
                                                                                                                       :> (Until
                                                                                                                             'V3
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NoBindingTeamMembers
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NonBindingTeam
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotConnected
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TeamNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("one2one"
                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                         'V2
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         NewConv
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                Conversation
                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   200
                                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                                   Conversation),
                                                                                                                                                                                              WithHeaders
                                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                                Conversation
                                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   201
                                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                                   Conversation)]
                                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                                               Conversation))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-one-to-one-conversation"
                                                                                                                    (Summary
                                                                                                                       "Create a 1:1 conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-created"
                                                                                                                         :> (From
                                                                                                                               'V3
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NoBindingTeamMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NonBindingTeam
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TeamNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> ("one2one"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           NewConv
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V3
                                                                                                                                                                                                     200
                                                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                                                     Conversation),
                                                                                                                                                                                                WithHeaders
                                                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                                                  Conversation
                                                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                                                     'V3
                                                                                                                                                                                                     201
                                                                                                                                                                                                     "Conversation created"
                                                                                                                                                                                                     Conversation)]
                                                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                                                 Conversation)))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation@v5"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V5
                                                                                                                               :> (Until
                                                                                                                                     'V6
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNotEnabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("one2one"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "usr"
                                                                                                                                                                 UserId
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[VersionedRespond
                                                                                                                                                                        'V5
                                                                                                                                                                        200
                                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                                        Conversation]
                                                                                                                                                                    Conversation))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V6
                                                                                                                                     :> (Until
                                                                                                                                           'V7
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'MLSNotEnabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("one2one"
                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                   "usr"
                                                                                                                                                                   UserId
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                             MLSPublicKey)]
                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                         MLSPublicKey))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-one-to-one-mls-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Get an MLS 1:1 conversation"
                                                                                                                                       :> (From
                                                                                                                                             'V7
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MLSNotEnabled
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotConnected
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> ("one2one"
                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> (QueryParam
                                                                                                                                                                         "format"
                                                                                                                                                                         MLSPublicKeyFormat
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'GET
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[Respond
                                                                                                                                                                                200
                                                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                                   SomeKey)]
                                                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                                                               SomeKey))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               Invite
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (Until
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "add-members-to-conversation"
                                                                                                                                                        (Summary
                                                                                                                                                           "Add qualified members to an existing conversation."
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (From
                                                                                                                                                                       'V2
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'AddConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'LeaveConversation)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'NotConnected
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               NonFederatingBackends
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V5
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "code-check"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Check validity of a conversation code."
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidConversationPassword
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> ("code-check"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationCode
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'POST
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Valid"]
                                                                                                                                                                                                            ()))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V4
                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V4
                                                                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                                                                 'WriteConversationsCode
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Delete conversation code"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'DELETE
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                                                                        Event]
                                                                                                                                                                                                                                    Event))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-code"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'GET
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "remove-member"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversations@v5" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ListConversations -> Sem r ConversationsResponse
listConversations))
    API
  (Named
     "list-conversations@v5"
     (Summary "Get conversation metadata for a list of conversation ids"
      :> (MakesFederatedCall 'Galley "get-conversations"
          :> (From 'V3
              :> (Until 'V6
                  :> (ZLocalUser
                      :> ("conversations"
                          :> ("list"
                              :> (ReqBody '[JSON] ListConversations
                                  :> MultiVerb
                                       'POST
                                       '[JSON]
                                       '[VersionedRespond
                                           'V5 200 "Conversation page" ConversationsResponse]
                                       ConversationsResponse)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "list-conversations"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list"
                             :> (ReqBody '[JSON] ListConversations
                                 :> Post '[JSON] ConversationsResponse)))))))
      :<|> (Named
              "get-conversation-by-reusable-code"
              (Summary "Get limited conversation information by key/code pair"
               :> (CanThrow 'CodeNotFound
                   :> (CanThrow 'InvalidConversationPassword
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'NotATeamMember
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("join"
                                                   :> (QueryParam' '[Required, Strict] "key" Key
                                                       :> (QueryParam'
                                                             '[Required, Strict] "code" Value
                                                           :> Get
                                                                '[JSON]
                                                                ConversationCoverView))))))))))))
            :<|> (Named
                    "create-group-conversation@v2"
                    (Summary "Create a new conversation"
                     :> (DescriptionOAuthScope 'WriteConversations
                         :> (MakesFederatedCall 'Brig "api-version"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (Until 'V3
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           UnreachableBackendsLegacy
                                                                         :> (Description
                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                             :> (ZLocalUser
                                                                                 :> (ZOptConn
                                                                                     :> ("conversations"
                                                                                         :> (VersionedReqBody
                                                                                               'V2
                                                                                               '[JSON]
                                                                                               NewConv
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         200
                                                                                                         "Conversation existed"
                                                                                                         Conversation),
                                                                                                    WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         201
                                                                                                         "Conversation created"
                                                                                                         Conversation)]
                                                                                                  (ResponseForExistedCreated
                                                                                                     Conversation))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation@v3"
                          (Summary "Create a new conversation"
                           :> (DescriptionOAuthScope 'WriteConversations
                               :> (MakesFederatedCall 'Brig "api-version"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V3
                                               :> (Until 'V4
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSNonEmptyMemberList
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'MissingLegalholdConsent
                                                                               :> (CanThrow
                                                                                     UnreachableBackendsLegacy
                                                                                   :> (Description
                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZOptConn
                                                                                               :> ("conversations"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         NewConv
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V3
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V3
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation)))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation@v5"
                                (Summary "Create a new conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V4
                                                     :> (Until 'V6
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'MissingLegalholdConsent
                                                                                     :> (CanThrow
                                                                                           NonFederatingBackends
                                                                                         :> (CanThrow
                                                                                               UnreachableBackends
                                                                                             :> (Description
                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   NewConv
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          CreateGroupConversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             CreateGroupConversation)]
                                                                                                                      CreateGroupConversationResponse)))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation"
                                      (Summary "Create a new conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall
                                                 'Brig "get-not-fully-connected-backends"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V6
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'MLSNonEmptyMemberList
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (Description
                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZOptConn
                                                                                                           :> ("conversations"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     NewConv
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            CreateGroupConversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               CreateGroupConversation)]
                                                                                                                        CreateGroupConversationResponse))))))))))))))))))))
                                    :<|> (Named
                                            "create-self-conversation@v2"
                                            (Summary "Create a self-conversation"
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("self"
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V2
                                                                         200
                                                                         "Conversation existed"
                                                                         Conversation),
                                                                    WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V2
                                                                         201
                                                                         "Conversation created"
                                                                         Conversation)]
                                                                  (ResponseForExistedCreated
                                                                     Conversation))))))
                                          :<|> (Named
                                                  "create-self-conversation@v5"
                                                  (Summary "Create a self-conversation"
                                                   :> (From 'V3
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("self"
                                                                       :> MultiVerb
                                                                            'POST
                                                                            '[JSON]
                                                                            '[WithHeaders
                                                                                ConversationHeaders
                                                                                Conversation
                                                                                (VersionedRespond
                                                                                   'V5
                                                                                   200
                                                                                   "Conversation existed"
                                                                                   Conversation),
                                                                              WithHeaders
                                                                                ConversationHeaders
                                                                                Conversation
                                                                                (VersionedRespond
                                                                                   'V5
                                                                                   201
                                                                                   "Conversation created"
                                                                                   Conversation)]
                                                                            (ResponseForExistedCreated
                                                                               Conversation)))))))
                                                :<|> (Named
                                                        "create-self-conversation"
                                                        (Summary "Create a self-conversation"
                                                         :> (From 'V6
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("self"
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V6
                                                                                     200
                                                                                     "Conversation existed"
                                                                                     Conversation),
                                                                                WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V6
                                                                                     201
                                                                                     "Conversation created"
                                                                                     Conversation)]
                                                                              (ResponseForExistedCreated
                                                                                 Conversation))))))
                                                      :<|> (Named
                                                              "get-mls-self-conversation@v5"
                                                              (Summary
                                                                 "Get the user's MLS self-conversation"
                                                               :> (From 'V5
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("mls-self"
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[VersionedRespond
                                                                                                'V5
                                                                                                200
                                                                                                "The MLS self-conversation"
                                                                                                Conversation]
                                                                                            Conversation)))))))
                                                            :<|> (Named
                                                                    "get-mls-self-conversation"
                                                                    (Summary
                                                                       "Get the user's MLS self-conversation"
                                                                     :> (From 'V6
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("mls-self"
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "The MLS self-conversation"
                                                                                                  Conversation]
                                                                                              Conversation))))))
                                                                  :<|> (Named
                                                                          "get-subconversation"
                                                                          (Summary
                                                                             "Get information about an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "get-sub-conversation"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSSubConvUnsupportedConvType
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("subconversations"
                                                                                                               :> (Capture
                                                                                                                     "subconv"
                                                                                                                     SubConvId
                                                                                                                   :> MultiVerb
                                                                                                                        'GET
                                                                                                                        '[JSON]
                                                                                                                        '[Respond
                                                                                                                            200
                                                                                                                            "Subconversation"
                                                                                                                            PublicSubConversation]
                                                                                                                        PublicSubConversation)))))))))))
                                                                        :<|> (Named
                                                                                "leave-subconversation"
                                                                                (Summary
                                                                                   "Leave an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "leave-sub-conversation"
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'MLSProtocolErrorTag
                                                                                                         :> (CanThrow
                                                                                                               'MLSStaleMessage
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZClient
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("subconversations"
                                                                                                                                     :> (Capture
                                                                                                                                           "subconv"
                                                                                                                                           SubConvId
                                                                                                                                         :> ("self"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'DELETE
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "OK"]
                                                                                                                                                  ()))))))))))))))))
                                                                              :<|> (Named
                                                                                      "delete-subconversation"
                                                                                      (Summary
                                                                                         "Delete an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "delete-sub-conversation"
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'MLSStaleMessage
                                                                                                               :> (ZLocalUser
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("subconversations"
                                                                                                                               :> (Capture
                                                                                                                                     "subconv"
                                                                                                                                     SubConvId
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         DeleteSubConversationRequest
                                                                                                                                       :> MultiVerb
                                                                                                                                            'DELETE
                                                                                                                                            '[JSON]
                                                                                                                                            '[Respond
                                                                                                                                                200
                                                                                                                                                "Deletion successful"
                                                                                                                                                ()]
                                                                                                                                            ())))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-subconversation-group-info"
                                                                                            (Summary
                                                                                               "Get MLS group information of subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "query-group-info"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'MLSMissingGroupInfo
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("subconversations"
                                                                                                                                 :> (Capture
                                                                                                                                       "subconv"
                                                                                                                                       SubConvId
                                                                                                                                     :> ("groupinfo"
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[MLS]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "The group information"
                                                                                                                                                  GroupInfoData]
                                                                                                                                              GroupInfoData))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-one-to-one-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a 1:1 conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-created"
                                                                                                           :> (Until
                                                                                                                 'V3
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NoBindingTeamMembers
                                                                                                                           :> (CanThrow
                                                                                                                                 'NonBindingTeam
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                             'V2
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             NewConv
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       200
                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                       Conversation),
                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       201
                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-one-to-one-conversation"
                                                                                                        (Summary
                                                                                                           "Create a 1:1 conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-created"
                                                                                                             :> (From
                                                                                                                   'V3
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'NoBindingTeamMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'NonBindingTeam
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               NewConv
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V3
                                                                                                                                                                                         200
                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                         Conversation),
                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V3
                                                                                                                                                                                         201
                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                     Conversation)))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNotEnabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("one2one"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "usr"
                                                                                                                                                     UserId
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[VersionedRespond
                                                                                                                                                            'V5
                                                                                                                                                            200
                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                            Conversation]
                                                                                                                                                        Conversation))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation@v6"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (Until
                                                                                                                               'V7
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNotEnabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("one2one"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "usr"
                                                                                                                                                       UserId
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                 MLSPublicKey)]
                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                             MLSPublicKey))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V7
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> ("one2one"
                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> (QueryParam
                                                                                                                                                             "format"
                                                                                                                                                             MLSPublicKeyFormat
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                       SomeKey)]
                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                   SomeKey))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (Until
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   Invite
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation-unqualified2"
                                                                                                                                      (Summary
                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (Until
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> ("v2"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (From
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Join a conversation using a reusable code"
                                                                                                                                                         :> (Description
                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "code-check"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Check validity of a conversation code."
                                                                                                                                                               :> (Description
                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> ("code-check"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationCode
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Valid"]
                                                                                                                                                                                                ()))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V4
                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V4
                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Delete conversation code"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                                                                            Event]
                                                                                                                                                                                                                        Event))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-code"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get existing conversation code"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                ())))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-member"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversations@v5"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V3
                 :> (Until 'V6
                     :> (ZLocalUser
                         :> ("conversations"
                             :> ("list"
                                 :> (ReqBody '[JSON] ListConversations
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[VersionedRespond
                                              'V5 200 "Conversation page" ConversationsResponse]
                                          ConversationsResponse))))))))
      :<|> (Named
              "list-conversations"
              (Summary "Get conversation metadata for a list of conversation ids"
               :> (MakesFederatedCall 'Galley "get-conversations"
                   :> (From 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("list"
                                   :> (ReqBody '[JSON] ListConversations
                                       :> Post '[JSON] ConversationsResponse)))))))
            :<|> (Named
                    "get-conversation-by-reusable-code"
                    (Summary "Get limited conversation information by key/code pair"
                     :> (CanThrow 'CodeNotFound
                         :> (CanThrow 'InvalidConversationPassword
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'NotATeamMember
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> ("join"
                                                         :> (QueryParam'
                                                               '[Required, Strict] "key" Key
                                                             :> (QueryParam'
                                                                   '[Required, Strict] "code" Value
                                                                 :> Get
                                                                      '[JSON]
                                                                      ConversationCoverView))))))))))))
                  :<|> (Named
                          "create-group-conversation@v2"
                          (Summary "Create a new conversation"
                           :> (DescriptionOAuthScope 'WriteConversations
                               :> (MakesFederatedCall 'Brig "api-version"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (Until 'V3
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'MLSNonEmptyMemberList
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 UnreachableBackendsLegacy
                                                                               :> (Description
                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZOptConn
                                                                                           :> ("conversations"
                                                                                               :> (VersionedReqBody
                                                                                                     'V2
                                                                                                     '[JSON]
                                                                                                     NewConv
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               200
                                                                                                               "Conversation existed"
                                                                                                               Conversation),
                                                                                                          WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               201
                                                                                                               "Conversation created"
                                                                                                               Conversation)]
                                                                                                        (ResponseForExistedCreated
                                                                                                           Conversation))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation@v3"
                                (Summary "Create a new conversation"
                                 :> (DescriptionOAuthScope 'WriteConversations
                                     :> (MakesFederatedCall 'Brig "api-version"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V3
                                                     :> (Until 'V4
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'MissingLegalholdConsent
                                                                                     :> (CanThrow
                                                                                           UnreachableBackendsLegacy
                                                                                         :> (Description
                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZOptConn
                                                                                                     :> ("conversations"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               NewConv
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V3
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V3
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         Conversation)]
                                                                                                                  (ResponseForExistedCreated
                                                                                                                     Conversation)))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation@v5"
                                      (Summary "Create a new conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall
                                                 'Brig "get-not-fully-connected-backends"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V4
                                                           :> (Until 'V6
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSNonEmptyMemberList
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'MissingLegalholdConsent
                                                                                           :> (CanThrow
                                                                                                 NonFederatingBackends
                                                                                               :> (CanThrow
                                                                                                     UnreachableBackends
                                                                                                   :> (Description
                                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         NewConv
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                CreateGroupConversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V5
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   CreateGroupConversation)]
                                                                                                                            CreateGroupConversationResponse)))))))))))))))))))))
                                    :<|> (Named
                                            "create-group-conversation"
                                            (Summary "Create a new conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Brig "get-not-fully-connected-backends"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-created"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (From 'V6
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow
                                                                           'MLSNonEmptyMemberList
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (Description
                                                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZOptConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           NewConv
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  Conversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     200
                                                                                                                                     "Conversation existed"
                                                                                                                                     Conversation),
                                                                                                                                WithHeaders
                                                                                                                                  ConversationHeaders
                                                                                                                                  CreateGroupConversation
                                                                                                                                  (VersionedRespond
                                                                                                                                     'V6
                                                                                                                                     201
                                                                                                                                     "Conversation created"
                                                                                                                                     CreateGroupConversation)]
                                                                                                                              CreateGroupConversationResponse))))))))))))))))))))
                                          :<|> (Named
                                                  "create-self-conversation@v2"
                                                  (Summary "Create a self-conversation"
                                                   :> (Until 'V3
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("self"
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V2
                                                                               200
                                                                               "Conversation existed"
                                                                               Conversation),
                                                                          WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V2
                                                                               201
                                                                               "Conversation created"
                                                                               Conversation)]
                                                                        (ResponseForExistedCreated
                                                                           Conversation))))))
                                                :<|> (Named
                                                        "create-self-conversation@v5"
                                                        (Summary "Create a self-conversation"
                                                         :> (From 'V3
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("self"
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V5
                                                                                         200
                                                                                         "Conversation existed"
                                                                                         Conversation),
                                                                                    WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V5
                                                                                         201
                                                                                         "Conversation created"
                                                                                         Conversation)]
                                                                                  (ResponseForExistedCreated
                                                                                     Conversation)))))))
                                                      :<|> (Named
                                                              "create-self-conversation"
                                                              (Summary "Create a self-conversation"
                                                               :> (From 'V6
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("self"
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V6
                                                                                           200
                                                                                           "Conversation existed"
                                                                                           Conversation),
                                                                                      WithHeaders
                                                                                        ConversationHeaders
                                                                                        Conversation
                                                                                        (VersionedRespond
                                                                                           'V6
                                                                                           201
                                                                                           "Conversation created"
                                                                                           Conversation)]
                                                                                    (ResponseForExistedCreated
                                                                                       Conversation))))))
                                                            :<|> (Named
                                                                    "get-mls-self-conversation@v5"
                                                                    (Summary
                                                                       "Get the user's MLS self-conversation"
                                                                     :> (From 'V5
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> ("mls-self"
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[VersionedRespond
                                                                                                      'V5
                                                                                                      200
                                                                                                      "The MLS self-conversation"
                                                                                                      Conversation]
                                                                                                  Conversation)))))))
                                                                  :<|> (Named
                                                                          "get-mls-self-conversation"
                                                                          (Summary
                                                                             "Get the user's MLS self-conversation"
                                                                           :> (From 'V6
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> ("mls-self"
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "The MLS self-conversation"
                                                                                                        Conversation]
                                                                                                    Conversation))))))
                                                                        :<|> (Named
                                                                                "get-subconversation"
                                                                                (Summary
                                                                                   "Get information about an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "get-sub-conversation"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'MLSSubConvUnsupportedConvType
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("subconversations"
                                                                                                                     :> (Capture
                                                                                                                           "subconv"
                                                                                                                           SubConvId
                                                                                                                         :> MultiVerb
                                                                                                                              'GET
                                                                                                                              '[JSON]
                                                                                                                              '[Respond
                                                                                                                                  200
                                                                                                                                  "Subconversation"
                                                                                                                                  PublicSubConversation]
                                                                                                                              PublicSubConversation)))))))))))
                                                                              :<|> (Named
                                                                                      "leave-subconversation"
                                                                                      (Summary
                                                                                         "Leave an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "leave-sub-conversation"
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'MLSProtocolErrorTag
                                                                                                               :> (CanThrow
                                                                                                                     'MLSStaleMessage
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZClient
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("subconversations"
                                                                                                                                           :> (Capture
                                                                                                                                                 "subconv"
                                                                                                                                                 SubConvId
                                                                                                                                               :> ("self"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'DELETE
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "OK"]
                                                                                                                                                        ()))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "delete-subconversation"
                                                                                            (Summary
                                                                                               "Delete an MLS subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "delete-sub-conversation"
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSStaleMessage
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("subconversations"
                                                                                                                                     :> (Capture
                                                                                                                                           "subconv"
                                                                                                                                           SubConvId
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               DeleteSubConversationRequest
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'DELETE
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[Respond
                                                                                                                                                      200
                                                                                                                                                      "Deletion successful"
                                                                                                                                                      ()]
                                                                                                                                                  ())))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-subconversation-group-info"
                                                                                                  (Summary
                                                                                                     "Get MLS group information of subconversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "query-group-info"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'MLSMissingGroupInfo
                                                                                                                   :> (CanThrow
                                                                                                                         'MLSNotEnabled
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("subconversations"
                                                                                                                                       :> (Capture
                                                                                                                                             "subconv"
                                                                                                                                             SubConvId
                                                                                                                                           :> ("groupinfo"
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[MLS]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "The group information"
                                                                                                                                                        GroupInfoData]
                                                                                                                                                    GroupInfoData))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-one-to-one-conversation@v2"
                                                                                                        (Summary
                                                                                                           "Create a 1:1 conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "api-version"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-created"
                                                                                                                 :> (Until
                                                                                                                       'V3
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NoBindingTeamMembers
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NonBindingTeam
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotConnected
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TeamNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("one2one"
                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                   'V2
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   NewConv
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             200
                                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                                             Conversation),
                                                                                                                                                                                        WithHeaders
                                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                                          Conversation
                                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                                             'V2
                                                                                                                                                                                             201
                                                                                                                                                                                             "Conversation created"
                                                                                                                                                                                             Conversation)]
                                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                                         Conversation))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-one-to-one-conversation"
                                                                                                              (Summary
                                                                                                                 "Create a 1:1 conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-created"
                                                                                                                   :> (From
                                                                                                                         'V3
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'NoBindingTeamMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NonBindingTeam
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> ("one2one"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     NewConv
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V3
                                                                                                                                                                                               200
                                                                                                                                                                                               "Conversation existed"
                                                                                                                                                                                               Conversation),
                                                                                                                                                                                          WithHeaders
                                                                                                                                                                                            ConversationHeaders
                                                                                                                                                                                            Conversation
                                                                                                                                                                                            (VersionedRespond
                                                                                                                                                                                               'V3
                                                                                                                                                                                               201
                                                                                                                                                                                               "Conversation created"
                                                                                                                                                                                               Conversation)]
                                                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                                                           Conversation)))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation@v5"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V5
                                                                                                                         :> (Until
                                                                                                                               'V6
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNotEnabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("one2one"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "usr"
                                                                                                                                                           UserId
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[VersionedRespond
                                                                                                                                                                  'V5
                                                                                                                                                                  200
                                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                                  Conversation]
                                                                                                                                                              Conversation))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation@v6"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V6
                                                                                                                               :> (Until
                                                                                                                                     'V7
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'MLSNotEnabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("one2one"
                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                             "usr"
                                                                                                                                                             UserId
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                       MLSPublicKey)]
                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                   MLSPublicKey))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-one-to-one-mls-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Get an MLS 1:1 conversation"
                                                                                                                                 :> (From
                                                                                                                                       'V7
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MLSNotEnabled
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotConnected
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> ("one2one"
                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> (QueryParam
                                                                                                                                                                   "format"
                                                                                                                                                                   MLSPublicKeyFormat
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'GET
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[Respond
                                                                                                                                                                          200
                                                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                                             SomeKey)]
                                                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                                                         SomeKey))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (Until
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         Invite
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation-unqualified2"
                                                                                                                                            (Summary
                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (Until
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> ("v2"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "add-members-to-conversation"
                                                                                                                                                  (Summary
                                                                                                                                                     "Add qualified members to an existing conversation."
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (From
                                                                                                                                                                 'V2
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'AddConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'LeaveConversation)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'NotConnected
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         NonFederatingBackends
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             UnreachableBackends
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V5
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Join a conversation using a reusable code"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "code-check"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Check validity of a conversation code."
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'CodeNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidConversationPassword
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> ("code-check"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationCode
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Valid"]
                                                                                                                                                                                                      ()))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V4
                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V4
                                                                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                                                                           'WriteConversationsCode
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-code-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Delete conversation code"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'DELETE
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                                                                  Event]
                                                                                                                                                                                                                              Event))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-code"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'GET
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "remove-member"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"list-conversations" (((HasAnnotation 'Remote "galley" "get-conversations",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> Dict (HasAnnotation 'Remote "galley" "get-conversations")
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ListConversations
 -> Sem
      '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ConversationsResponse)
-> QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ListConversations
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationsResponse
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member FederatorAccess r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ListConversations -> Sem r ConversationsResponse
listConversations))
    API
  (Named
     "list-conversations"
     (Summary "Get conversation metadata for a list of conversation ids"
      :> (MakesFederatedCall 'Galley "get-conversations"
          :> (From 'V6
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("list"
                          :> (ReqBody '[JSON] ListConversations
                              :> Post '[JSON] ConversationsResponse))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation-by-reusable-code"
        (Summary "Get limited conversation information by key/code pair"
         :> (CanThrow 'CodeNotFound
             :> (CanThrow 'InvalidConversationPassword
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'NotATeamMember
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("join"
                                             :> (QueryParam' '[Required, Strict] "key" Key
                                                 :> (QueryParam' '[Required, Strict] "code" Value
                                                     :> Get
                                                          '[JSON] ConversationCoverView))))))))))))
      :<|> (Named
              "create-group-conversation@v2"
              (Summary "Create a new conversation"
               :> (DescriptionOAuthScope 'WriteConversations
                   :> (MakesFederatedCall 'Brig "api-version"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (Until 'V3
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'MLSNonEmptyMemberList
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow
                                                                     UnreachableBackendsLegacy
                                                                   :> (Description
                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                       :> (ZLocalUser
                                                                           :> (ZOptConn
                                                                               :> ("conversations"
                                                                                   :> (VersionedReqBody
                                                                                         'V2
                                                                                         '[JSON]
                                                                                         NewConv
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   200
                                                                                                   "Conversation existed"
                                                                                                   Conversation),
                                                                                              WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   201
                                                                                                   "Conversation created"
                                                                                                   Conversation)]
                                                                                            (ResponseForExistedCreated
                                                                                               Conversation))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation@v3"
                    (Summary "Create a new conversation"
                     :> (DescriptionOAuthScope 'WriteConversations
                         :> (MakesFederatedCall 'Brig "api-version"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V3
                                         :> (Until 'V4
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSNonEmptyMemberList
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow
                                                                           'MissingLegalholdConsent
                                                                         :> (CanThrow
                                                                               UnreachableBackendsLegacy
                                                                             :> (Description
                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZOptConn
                                                                                         :> ("conversations"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   NewConv
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V3
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V3
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation)))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation@v5"
                          (Summary "Create a new conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V4
                                               :> (Until 'V6
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSNonEmptyMemberList
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'MissingLegalholdConsent
                                                                               :> (CanThrow
                                                                                     NonFederatingBackends
                                                                                   :> (CanThrow
                                                                                         UnreachableBackends
                                                                                       :> (Description
                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             NewConv
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    CreateGroupConversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       CreateGroupConversation)]
                                                                                                                CreateGroupConversationResponse)))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation"
                                (Summary "Create a new conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V6
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'MLSNonEmptyMemberList
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (Description
                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZOptConn
                                                                                                     :> ("conversations"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               NewConv
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      CreateGroupConversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         CreateGroupConversation)]
                                                                                                                  CreateGroupConversationResponse))))))))))))))))))))
                              :<|> (Named
                                      "create-self-conversation@v2"
                                      (Summary "Create a self-conversation"
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("self"
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V2
                                                                   200
                                                                   "Conversation existed"
                                                                   Conversation),
                                                              WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V2
                                                                   201
                                                                   "Conversation created"
                                                                   Conversation)]
                                                            (ResponseForExistedCreated
                                                               Conversation))))))
                                    :<|> (Named
                                            "create-self-conversation@v5"
                                            (Summary "Create a self-conversation"
                                             :> (From 'V3
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("self"
                                                                 :> MultiVerb
                                                                      'POST
                                                                      '[JSON]
                                                                      '[WithHeaders
                                                                          ConversationHeaders
                                                                          Conversation
                                                                          (VersionedRespond
                                                                             'V5
                                                                             200
                                                                             "Conversation existed"
                                                                             Conversation),
                                                                        WithHeaders
                                                                          ConversationHeaders
                                                                          Conversation
                                                                          (VersionedRespond
                                                                             'V5
                                                                             201
                                                                             "Conversation created"
                                                                             Conversation)]
                                                                      (ResponseForExistedCreated
                                                                         Conversation)))))))
                                          :<|> (Named
                                                  "create-self-conversation"
                                                  (Summary "Create a self-conversation"
                                                   :> (From 'V6
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("self"
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V6
                                                                               200
                                                                               "Conversation existed"
                                                                               Conversation),
                                                                          WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V6
                                                                               201
                                                                               "Conversation created"
                                                                               Conversation)]
                                                                        (ResponseForExistedCreated
                                                                           Conversation))))))
                                                :<|> (Named
                                                        "get-mls-self-conversation@v5"
                                                        (Summary
                                                           "Get the user's MLS self-conversation"
                                                         :> (From 'V5
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("mls-self"
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[VersionedRespond
                                                                                          'V5
                                                                                          200
                                                                                          "The MLS self-conversation"
                                                                                          Conversation]
                                                                                      Conversation)))))))
                                                      :<|> (Named
                                                              "get-mls-self-conversation"
                                                              (Summary
                                                                 "Get the user's MLS self-conversation"
                                                               :> (From 'V6
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("mls-self"
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "The MLS self-conversation"
                                                                                            Conversation]
                                                                                        Conversation))))))
                                                            :<|> (Named
                                                                    "get-subconversation"
                                                                    (Summary
                                                                       "Get information about an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "get-sub-conversation"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSSubConvUnsupportedConvType
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("subconversations"
                                                                                                         :> (Capture
                                                                                                               "subconv"
                                                                                                               SubConvId
                                                                                                             :> MultiVerb
                                                                                                                  'GET
                                                                                                                  '[JSON]
                                                                                                                  '[Respond
                                                                                                                      200
                                                                                                                      "Subconversation"
                                                                                                                      PublicSubConversation]
                                                                                                                  PublicSubConversation)))))))))))
                                                                  :<|> (Named
                                                                          "leave-subconversation"
                                                                          (Summary
                                                                             "Leave an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "leave-sub-conversation"
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'MLSProtocolErrorTag
                                                                                                   :> (CanThrow
                                                                                                         'MLSStaleMessage
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZClient
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("subconversations"
                                                                                                                               :> (Capture
                                                                                                                                     "subconv"
                                                                                                                                     SubConvId
                                                                                                                                   :> ("self"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'DELETE
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "OK"]
                                                                                                                                            ()))))))))))))))))
                                                                        :<|> (Named
                                                                                "delete-subconversation"
                                                                                (Summary
                                                                                   "Delete an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "delete-sub-conversation"
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'MLSStaleMessage
                                                                                                         :> (ZLocalUser
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("subconversations"
                                                                                                                         :> (Capture
                                                                                                                               "subconv"
                                                                                                                               SubConvId
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   DeleteSubConversationRequest
                                                                                                                                 :> MultiVerb
                                                                                                                                      'DELETE
                                                                                                                                      '[JSON]
                                                                                                                                      '[Respond
                                                                                                                                          200
                                                                                                                                          "Deletion successful"
                                                                                                                                          ()]
                                                                                                                                      ())))))))))))))
                                                                              :<|> (Named
                                                                                      "get-subconversation-group-info"
                                                                                      (Summary
                                                                                         "Get MLS group information of subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "query-group-info"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'MLSMissingGroupInfo
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("subconversations"
                                                                                                                           :> (Capture
                                                                                                                                 "subconv"
                                                                                                                                 SubConvId
                                                                                                                               :> ("groupinfo"
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[MLS]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "The group information"
                                                                                                                                            GroupInfoData]
                                                                                                                                        GroupInfoData))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-one-to-one-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a 1:1 conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-created"
                                                                                                     :> (Until
                                                                                                           'V3
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NoBindingTeamMembers
                                                                                                                     :> (CanThrow
                                                                                                                           'NonBindingTeam
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("one2one"
                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                       'V2
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       NewConv
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 200
                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                 Conversation),
                                                                                                                                                                            WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 201
                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                 Conversation)]
                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-one-to-one-conversation"
                                                                                                  (Summary
                                                                                                     "Create a 1:1 conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-created"
                                                                                                       :> (From
                                                                                                             'V3
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'NoBindingTeamMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'NonBindingTeam
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                               :> (CanThrow
                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("one2one"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         NewConv
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V3
                                                                                                                                                                                   200
                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                   Conversation),
                                                                                                                                                                              WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V3
                                                                                                                                                                                   201
                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                   Conversation)]
                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                               Conversation)))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNotEnabled
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("one2one"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "usr"
                                                                                                                                               UserId
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[VersionedRespond
                                                                                                                                                      'V5
                                                                                                                                                      200
                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                      Conversation]
                                                                                                                                                  Conversation))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation@v6"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (Until
                                                                                                                         'V7
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNotEnabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("one2one"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "usr"
                                                                                                                                                 UserId
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                           MLSPublicKey)]
                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                       MLSPublicKey))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V7
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> ("one2one"
                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> (QueryParam
                                                                                                                                                       "format"
                                                                                                                                                       MLSPublicKeyFormat
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                 SomeKey)]
                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                             SomeKey))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Add members to an existing conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (Until
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             Invite
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation-unqualified2"
                                                                                                                                (Summary
                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (Until
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> ("v2"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (From
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "join-conversation-by-id-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                             :> (Until
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Join a conversation using a reusable code"
                                                                                                                                                   :> (Description
                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CodeNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "code-check"
                                                                                                                                                        (Summary
                                                                                                                                                           "Check validity of a conversation code."
                                                                                                                                                         :> (Description
                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> ("code-check"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationCode
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Valid"]
                                                                                                                                                                                          ()))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V4
                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V4
                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Delete conversation code"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                                                                      Event]
                                                                                                                                                                                                                  Event))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-code"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get existing conversation code"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "member-typing-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                          ())))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-member"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-other-member"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "list-conversations"
        (Summary "Get conversation metadata for a list of conversation ids"
         :> (MakesFederatedCall 'Galley "get-conversations"
             :> (From 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("list"
                             :> (ReqBody '[JSON] ListConversations
                                 :> Post '[JSON] ConversationsResponse)))))))
      :<|> (Named
              "get-conversation-by-reusable-code"
              (Summary "Get limited conversation information by key/code pair"
               :> (CanThrow 'CodeNotFound
                   :> (CanThrow 'InvalidConversationPassword
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'NotATeamMember
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> ("join"
                                                   :> (QueryParam' '[Required, Strict] "key" Key
                                                       :> (QueryParam'
                                                             '[Required, Strict] "code" Value
                                                           :> Get
                                                                '[JSON]
                                                                ConversationCoverView))))))))))))
            :<|> (Named
                    "create-group-conversation@v2"
                    (Summary "Create a new conversation"
                     :> (DescriptionOAuthScope 'WriteConversations
                         :> (MakesFederatedCall 'Brig "api-version"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (Until 'V3
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           UnreachableBackendsLegacy
                                                                         :> (Description
                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                             :> (ZLocalUser
                                                                                 :> (ZOptConn
                                                                                     :> ("conversations"
                                                                                         :> (VersionedReqBody
                                                                                               'V2
                                                                                               '[JSON]
                                                                                               NewConv
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         200
                                                                                                         "Conversation existed"
                                                                                                         Conversation),
                                                                                                    WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         201
                                                                                                         "Conversation created"
                                                                                                         Conversation)]
                                                                                                  (ResponseForExistedCreated
                                                                                                     Conversation))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation@v3"
                          (Summary "Create a new conversation"
                           :> (DescriptionOAuthScope 'WriteConversations
                               :> (MakesFederatedCall 'Brig "api-version"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V3
                                               :> (Until 'V4
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSNonEmptyMemberList
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'MissingLegalholdConsent
                                                                               :> (CanThrow
                                                                                     UnreachableBackendsLegacy
                                                                                   :> (Description
                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZOptConn
                                                                                               :> ("conversations"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         NewConv
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V3
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V3
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   Conversation)]
                                                                                                            (ResponseForExistedCreated
                                                                                                               Conversation)))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation@v5"
                                (Summary "Create a new conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V4
                                                     :> (Until 'V6
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'MissingLegalholdConsent
                                                                                     :> (CanThrow
                                                                                           NonFederatingBackends
                                                                                         :> (CanThrow
                                                                                               UnreachableBackends
                                                                                             :> (Description
                                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   NewConv
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          CreateGroupConversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V5
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             CreateGroupConversation)]
                                                                                                                      CreateGroupConversationResponse)))))))))))))))))))))
                              :<|> (Named
                                      "create-group-conversation"
                                      (Summary "Create a new conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall
                                                 'Brig "get-not-fully-connected-backends"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-created"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (From 'V6
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'MLSNonEmptyMemberList
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (Description
                                                                                                     "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZOptConn
                                                                                                           :> ("conversations"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     NewConv
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            Conversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               200
                                                                                                                               "Conversation existed"
                                                                                                                               Conversation),
                                                                                                                          WithHeaders
                                                                                                                            ConversationHeaders
                                                                                                                            CreateGroupConversation
                                                                                                                            (VersionedRespond
                                                                                                                               'V6
                                                                                                                               201
                                                                                                                               "Conversation created"
                                                                                                                               CreateGroupConversation)]
                                                                                                                        CreateGroupConversationResponse))))))))))))))))))))
                                    :<|> (Named
                                            "create-self-conversation@v2"
                                            (Summary "Create a self-conversation"
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("self"
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V2
                                                                         200
                                                                         "Conversation existed"
                                                                         Conversation),
                                                                    WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V2
                                                                         201
                                                                         "Conversation created"
                                                                         Conversation)]
                                                                  (ResponseForExistedCreated
                                                                     Conversation))))))
                                          :<|> (Named
                                                  "create-self-conversation@v5"
                                                  (Summary "Create a self-conversation"
                                                   :> (From 'V3
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("self"
                                                                       :> MultiVerb
                                                                            'POST
                                                                            '[JSON]
                                                                            '[WithHeaders
                                                                                ConversationHeaders
                                                                                Conversation
                                                                                (VersionedRespond
                                                                                   'V5
                                                                                   200
                                                                                   "Conversation existed"
                                                                                   Conversation),
                                                                              WithHeaders
                                                                                ConversationHeaders
                                                                                Conversation
                                                                                (VersionedRespond
                                                                                   'V5
                                                                                   201
                                                                                   "Conversation created"
                                                                                   Conversation)]
                                                                            (ResponseForExistedCreated
                                                                               Conversation)))))))
                                                :<|> (Named
                                                        "create-self-conversation"
                                                        (Summary "Create a self-conversation"
                                                         :> (From 'V6
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("self"
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V6
                                                                                     200
                                                                                     "Conversation existed"
                                                                                     Conversation),
                                                                                WithHeaders
                                                                                  ConversationHeaders
                                                                                  Conversation
                                                                                  (VersionedRespond
                                                                                     'V6
                                                                                     201
                                                                                     "Conversation created"
                                                                                     Conversation)]
                                                                              (ResponseForExistedCreated
                                                                                 Conversation))))))
                                                      :<|> (Named
                                                              "get-mls-self-conversation@v5"
                                                              (Summary
                                                                 "Get the user's MLS self-conversation"
                                                               :> (From 'V5
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> ("mls-self"
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[VersionedRespond
                                                                                                'V5
                                                                                                200
                                                                                                "The MLS self-conversation"
                                                                                                Conversation]
                                                                                            Conversation)))))))
                                                            :<|> (Named
                                                                    "get-mls-self-conversation"
                                                                    (Summary
                                                                       "Get the user's MLS self-conversation"
                                                                     :> (From 'V6
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> ("mls-self"
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "The MLS self-conversation"
                                                                                                  Conversation]
                                                                                              Conversation))))))
                                                                  :<|> (Named
                                                                          "get-subconversation"
                                                                          (Summary
                                                                             "Get information about an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "get-sub-conversation"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'MLSSubConvUnsupportedConvType
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("subconversations"
                                                                                                               :> (Capture
                                                                                                                     "subconv"
                                                                                                                     SubConvId
                                                                                                                   :> MultiVerb
                                                                                                                        'GET
                                                                                                                        '[JSON]
                                                                                                                        '[Respond
                                                                                                                            200
                                                                                                                            "Subconversation"
                                                                                                                            PublicSubConversation]
                                                                                                                        PublicSubConversation)))))))))))
                                                                        :<|> (Named
                                                                                "leave-subconversation"
                                                                                (Summary
                                                                                   "Leave an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "leave-sub-conversation"
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'MLSProtocolErrorTag
                                                                                                         :> (CanThrow
                                                                                                               'MLSStaleMessage
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZClient
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("subconversations"
                                                                                                                                     :> (Capture
                                                                                                                                           "subconv"
                                                                                                                                           SubConvId
                                                                                                                                         :> ("self"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'DELETE
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "OK"]
                                                                                                                                                  ()))))))))))))))))
                                                                              :<|> (Named
                                                                                      "delete-subconversation"
                                                                                      (Summary
                                                                                         "Delete an MLS subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "delete-sub-conversation"
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (CanThrow
                                                                                                                 'MLSStaleMessage
                                                                                                               :> (ZLocalUser
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("subconversations"
                                                                                                                               :> (Capture
                                                                                                                                     "subconv"
                                                                                                                                     SubConvId
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         DeleteSubConversationRequest
                                                                                                                                       :> MultiVerb
                                                                                                                                            'DELETE
                                                                                                                                            '[JSON]
                                                                                                                                            '[Respond
                                                                                                                                                200
                                                                                                                                                "Deletion successful"
                                                                                                                                                ()]
                                                                                                                                            ())))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-subconversation-group-info"
                                                                                            (Summary
                                                                                               "Get MLS group information of subconversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "query-group-info"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'MLSMissingGroupInfo
                                                                                                             :> (CanThrow
                                                                                                                   'MLSNotEnabled
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("subconversations"
                                                                                                                                 :> (Capture
                                                                                                                                       "subconv"
                                                                                                                                       SubConvId
                                                                                                                                     :> ("groupinfo"
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[MLS]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "The group information"
                                                                                                                                                  GroupInfoData]
                                                                                                                                              GroupInfoData))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-one-to-one-conversation@v2"
                                                                                                  (Summary
                                                                                                     "Create a 1:1 conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "api-version"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-created"
                                                                                                           :> (Until
                                                                                                                 'V3
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NoBindingTeamMembers
                                                                                                                           :> (CanThrow
                                                                                                                                 'NonBindingTeam
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotConnected
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TeamNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("one2one"
                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                             'V2
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             NewConv
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       200
                                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                                       Conversation),
                                                                                                                                                                                  WithHeaders
                                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                                    Conversation
                                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                                       'V2
                                                                                                                                                                                       201
                                                                                                                                                                                       "Conversation created"
                                                                                                                                                                                       Conversation)]
                                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                                   Conversation))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-one-to-one-conversation"
                                                                                                        (Summary
                                                                                                           "Create a 1:1 conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-created"
                                                                                                             :> (From
                                                                                                                   'V3
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'NoBindingTeamMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'NonBindingTeam
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           UnreachableBackendsLegacy
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> ("one2one"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               NewConv
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V3
                                                                                                                                                                                         200
                                                                                                                                                                                         "Conversation existed"
                                                                                                                                                                                         Conversation),
                                                                                                                                                                                    WithHeaders
                                                                                                                                                                                      ConversationHeaders
                                                                                                                                                                                      Conversation
                                                                                                                                                                                      (VersionedRespond
                                                                                                                                                                                         'V3
                                                                                                                                                                                         201
                                                                                                                                                                                         "Conversation created"
                                                                                                                                                                                         Conversation)]
                                                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                                                     Conversation)))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation@v5"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V5
                                                                                                                   :> (Until
                                                                                                                         'V6
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNotEnabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("one2one"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "usr"
                                                                                                                                                     UserId
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[VersionedRespond
                                                                                                                                                            'V5
                                                                                                                                                            200
                                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                                            Conversation]
                                                                                                                                                        Conversation))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation@v6"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V6
                                                                                                                         :> (Until
                                                                                                                               'V7
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'MLSNotEnabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("one2one"
                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                       "usr"
                                                                                                                                                       UserId
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                 MLSPublicKey)]
                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                             MLSPublicKey))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-one-to-one-mls-conversation"
                                                                                                                          (Summary
                                                                                                                             "Get an MLS 1:1 conversation"
                                                                                                                           :> (From
                                                                                                                                 'V7
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MLSNotEnabled
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotConnected
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> ("one2one"
                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> (QueryParam
                                                                                                                                                             "format"
                                                                                                                                                             MLSPublicKeyFormat
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'GET
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[Respond
                                                                                                                                                                    200
                                                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                                       SomeKey)]
                                                                                                                                                                (MLSOne2OneConversation
                                                                                                                                                                   SomeKey))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (Until
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   Invite
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation-unqualified2"
                                                                                                                                      (Summary
                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (Until
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> ("v2"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "add-members-to-conversation"
                                                                                                                                            (Summary
                                                                                                                                               "Add qualified members to an existing conversation."
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (From
                                                                                                                                                           'V2
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'AddConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'LeaveConversation)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'TooManyMembers
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'NotConnected
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   NonFederatingBackends
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       UnreachableBackends
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V5
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("join"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Join a conversation using a reusable code"
                                                                                                                                                         :> (Description
                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> ("join"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "code-check"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Check validity of a conversation code."
                                                                                                                                                               :> (Description
                                                                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'CodeNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidConversationPassword
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> ("code-check"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationCode
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Valid"]
                                                                                                                                                                                                ()))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V4
                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Create or recreate a conversation code"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V4
                                                                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                                                                     'WriteConversationsCode
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZOptConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-code-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Delete conversation code"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'DELETE
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                                                                            Event]
                                                                                                                                                                                                                        Event))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-code"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get existing conversation code"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'GET
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                                ())))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "remove-member"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation-by-reusable-code" ServerT
  (Summary "Get limited conversation information by key/code pair"
   :> (CanThrow 'CodeNotFound
       :> (CanThrow 'InvalidConversationPassword
           :> (CanThrow 'ConvNotFound
               :> (CanThrow 'ConvAccessDenied
                   :> (CanThrow 'GuestLinksDisabled
                       :> (CanThrow 'NotATeamMember
                           :> (ZLocalUser
                               :> ("conversations"
                                   :> ("join"
                                       :> (QueryParam' '[Required, Strict] "key" Key
                                           :> (QueryParam' '[Required, Strict] "code" Value
                                               :> Get '[JSON] ConversationCoverView))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get limited conversation information by key/code pair"
            :> (CanThrow 'CodeNotFound
                :> (CanThrow 'InvalidConversationPassword
                    :> (CanThrow 'ConvNotFound
                        :> (CanThrow 'ConvAccessDenied
                            :> (CanThrow 'GuestLinksDisabled
                                :> (CanThrow 'NotATeamMember
                                    :> (ZLocalUser
                                        :> ("conversations"
                                            :> ("join"
                                                :> (QueryParam' '[Required, Strict] "key" Key
                                                    :> (QueryParam' '[Required, Strict] "code" Value
                                                        :> Get
                                                             '[JSON]
                                                             ConversationCoverView)))))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Key
-> Value
-> Sem
     '[Error (Tagged 'CodeNotFound ()),
       Error (Tagged 'InvalidConversationPassword ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'NotATeamMember ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationCoverView
forall (r :: EffectRow).
(Member BrigAccess r, Member CodeStore r,
 Member ConversationStore r,
 Member (Error (Tagged 'CodeNotFound ())) r,
 Member (Error (Tagged 'InvalidConversationPassword ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'GuestLinksDisabled ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r, Member TeamStore r,
 Member TeamFeatureStore r, Member (Input Opts) r) =>
QualifiedWithTag 'QLocal UserId
-> Key -> Value -> Sem r ConversationCoverView
getConversationByReusableCode
    API
  (Named
     "get-conversation-by-reusable-code"
     (Summary "Get limited conversation information by key/code pair"
      :> (CanThrow 'CodeNotFound
          :> (CanThrow 'InvalidConversationPassword
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'ConvAccessDenied
                      :> (CanThrow 'GuestLinksDisabled
                          :> (CanThrow 'NotATeamMember
                              :> (ZLocalUser
                                  :> ("conversations"
                                      :> ("join"
                                          :> (QueryParam' '[Required, Strict] "key" Key
                                              :> (QueryParam' '[Required, Strict] "code" Value
                                                  :> Get '[JSON] ConversationCoverView)))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-group-conversation@v2"
        (Summary "Create a new conversation"
         :> (DescriptionOAuthScope 'WriteConversations
             :> (MakesFederatedCall 'Brig "api-version"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (Until 'V3
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'MLSNonEmptyMemberList
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow UnreachableBackendsLegacy
                                                             :> (Description
                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                 :> (ZLocalUser
                                                                     :> (ZOptConn
                                                                         :> ("conversations"
                                                                             :> (VersionedReqBody
                                                                                   'V2
                                                                                   '[JSON]
                                                                                   NewConv
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             200
                                                                                             "Conversation existed"
                                                                                             Conversation),
                                                                                        WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             201
                                                                                             "Conversation created"
                                                                                             Conversation)]
                                                                                      (ResponseForExistedCreated
                                                                                         Conversation))))))))))))))))))))
      :<|> (Named
              "create-group-conversation@v3"
              (Summary "Create a new conversation"
               :> (DescriptionOAuthScope 'WriteConversations
                   :> (MakesFederatedCall 'Brig "api-version"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V3
                                   :> (Until 'V4
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSNonEmptyMemberList
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'MissingLegalholdConsent
                                                                   :> (CanThrow
                                                                         UnreachableBackendsLegacy
                                                                       :> (Description
                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                           :> (ZLocalUser
                                                                               :> (ZOptConn
                                                                                   :> ("conversations"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             NewConv
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V3
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V3
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation)))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation@v5"
                    (Summary "Create a new conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V4
                                         :> (Until 'V6
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSNonEmptyMemberList
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow
                                                                           'MissingLegalholdConsent
                                                                         :> (CanThrow
                                                                               NonFederatingBackends
                                                                             :> (CanThrow
                                                                                   UnreachableBackends
                                                                                 :> (Description
                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       NewConv
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              CreateGroupConversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 CreateGroupConversation)]
                                                                                                          CreateGroupConversationResponse)))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation"
                          (Summary "Create a new conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V6
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'MLSNonEmptyMemberList
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (Description
                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZOptConn
                                                                                               :> ("conversations"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         NewConv
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                CreateGroupConversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   CreateGroupConversation)]
                                                                                                            CreateGroupConversationResponse))))))))))))))))))))
                        :<|> (Named
                                "create-self-conversation@v2"
                                (Summary "Create a self-conversation"
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("self"
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V2
                                                             200
                                                             "Conversation existed"
                                                             Conversation),
                                                        WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V2
                                                             201
                                                             "Conversation created"
                                                             Conversation)]
                                                      (ResponseForExistedCreated Conversation))))))
                              :<|> (Named
                                      "create-self-conversation@v5"
                                      (Summary "Create a self-conversation"
                                       :> (From 'V3
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("self"
                                                           :> MultiVerb
                                                                'POST
                                                                '[JSON]
                                                                '[WithHeaders
                                                                    ConversationHeaders
                                                                    Conversation
                                                                    (VersionedRespond
                                                                       'V5
                                                                       200
                                                                       "Conversation existed"
                                                                       Conversation),
                                                                  WithHeaders
                                                                    ConversationHeaders
                                                                    Conversation
                                                                    (VersionedRespond
                                                                       'V5
                                                                       201
                                                                       "Conversation created"
                                                                       Conversation)]
                                                                (ResponseForExistedCreated
                                                                   Conversation)))))))
                                    :<|> (Named
                                            "create-self-conversation"
                                            (Summary "Create a self-conversation"
                                             :> (From 'V6
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("self"
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V6
                                                                         200
                                                                         "Conversation existed"
                                                                         Conversation),
                                                                    WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V6
                                                                         201
                                                                         "Conversation created"
                                                                         Conversation)]
                                                                  (ResponseForExistedCreated
                                                                     Conversation))))))
                                          :<|> (Named
                                                  "get-mls-self-conversation@v5"
                                                  (Summary "Get the user's MLS self-conversation"
                                                   :> (From 'V5
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("mls-self"
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[VersionedRespond
                                                                                    'V5
                                                                                    200
                                                                                    "The MLS self-conversation"
                                                                                    Conversation]
                                                                                Conversation)))))))
                                                :<|> (Named
                                                        "get-mls-self-conversation"
                                                        (Summary
                                                           "Get the user's MLS self-conversation"
                                                         :> (From 'V6
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("mls-self"
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "The MLS self-conversation"
                                                                                      Conversation]
                                                                                  Conversation))))))
                                                      :<|> (Named
                                                              "get-subconversation"
                                                              (Summary
                                                                 "Get information about an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "get-sub-conversation"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSSubConvUnsupportedConvType
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("subconversations"
                                                                                                   :> (Capture
                                                                                                         "subconv"
                                                                                                         SubConvId
                                                                                                       :> MultiVerb
                                                                                                            'GET
                                                                                                            '[JSON]
                                                                                                            '[Respond
                                                                                                                200
                                                                                                                "Subconversation"
                                                                                                                PublicSubConversation]
                                                                                                            PublicSubConversation)))))))))))
                                                            :<|> (Named
                                                                    "leave-subconversation"
                                                                    (Summary
                                                                       "Leave an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "leave-sub-conversation"
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'MLSProtocolErrorTag
                                                                                             :> (CanThrow
                                                                                                   'MLSStaleMessage
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZClient
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("subconversations"
                                                                                                                         :> (Capture
                                                                                                                               "subconv"
                                                                                                                               SubConvId
                                                                                                                             :> ("self"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'DELETE
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "OK"]
                                                                                                                                      ()))))))))))))))))
                                                                  :<|> (Named
                                                                          "delete-subconversation"
                                                                          (Summary
                                                                             "Delete an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "delete-sub-conversation"
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'MLSStaleMessage
                                                                                                   :> (ZLocalUser
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("subconversations"
                                                                                                                   :> (Capture
                                                                                                                         "subconv"
                                                                                                                         SubConvId
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             DeleteSubConversationRequest
                                                                                                                           :> MultiVerb
                                                                                                                                'DELETE
                                                                                                                                '[JSON]
                                                                                                                                '[Respond
                                                                                                                                    200
                                                                                                                                    "Deletion successful"
                                                                                                                                    ()]
                                                                                                                                ())))))))))))))
                                                                        :<|> (Named
                                                                                "get-subconversation-group-info"
                                                                                (Summary
                                                                                   "Get MLS group information of subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "query-group-info"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'MLSMissingGroupInfo
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("subconversations"
                                                                                                                     :> (Capture
                                                                                                                           "subconv"
                                                                                                                           SubConvId
                                                                                                                         :> ("groupinfo"
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[MLS]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "The group information"
                                                                                                                                      GroupInfoData]
                                                                                                                                  GroupInfoData))))))))))))
                                                                              :<|> (Named
                                                                                      "create-one-to-one-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a 1:1 conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-created"
                                                                                               :> (Until
                                                                                                     'V3
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NoBindingTeamMembers
                                                                                                               :> (CanThrow
                                                                                                                     'NonBindingTeam
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("one2one"
                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                 'V2
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 NewConv
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           200
                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                           Conversation),
                                                                                                                                                                      WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           201
                                                                                                                                                                           "Conversation created"
                                                                                                                                                                           Conversation)]
                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-one-to-one-conversation"
                                                                                            (Summary
                                                                                               "Create a 1:1 conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-created"
                                                                                                 :> (From
                                                                                                       'V3
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'NoBindingTeamMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'NonBindingTeam
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                         :> (CanThrow
                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("one2one"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   NewConv
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V3
                                                                                                                                                                             200
                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                             Conversation),
                                                                                                                                                                        WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V3
                                                                                                                                                                             201
                                                                                                                                                                             "Conversation created"
                                                                                                                                                                             Conversation)]
                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                         Conversation)))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNotEnabled
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSFederatedOne2OneNotSupported
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("one2one"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "usr"
                                                                                                                                         UserId
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[VersionedRespond
                                                                                                                                                'V5
                                                                                                                                                200
                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                Conversation]
                                                                                                                                            Conversation))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation@v6"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (Until
                                                                                                                   'V7
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNotEnabled
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("one2one"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "usr"
                                                                                                                                           UserId
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                     MLSPublicKey)]
                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                 MLSPublicKey))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V7
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> ("conversations"
                                                                                                                                   :> ("one2one"
                                                                                                                                       :> (QualifiedCapture
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> (QueryParam
                                                                                                                                                 "format"
                                                                                                                                                 MLSPublicKeyFormat
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                           SomeKey)]
                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                       SomeKey))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Add members to an existing conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (Until
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       Invite
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation-unqualified2"
                                                                                                                          (Summary
                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (Until
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> ("v2"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (From
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "join-conversation-by-id-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                       :> (Until
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotATeamMember
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "join-conversation-by-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Join a conversation using a reusable code"
                                                                                                                                             :> (Description
                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CodeNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           JoinConversationByCode
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "code-check"
                                                                                                                                                  (Summary
                                                                                                                                                     "Check validity of a conversation code."
                                                                                                                                                   :> (Description
                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'CodeNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> ("code-check"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationCode
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Valid"]
                                                                                                                                                                                    ()))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V4
                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-conversation-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V4
                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Delete conversation code"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'DELETE
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                                                                Event]
                                                                                                                                                                                                            Event))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-code"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get existing conversation code"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "member-typing-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                    ())))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "member-typing-qualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-member"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-other-member"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation-by-reusable-code"
        (Summary "Get limited conversation information by key/code pair"
         :> (CanThrow 'CodeNotFound
             :> (CanThrow 'InvalidConversationPassword
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'NotATeamMember
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> ("join"
                                             :> (QueryParam' '[Required, Strict] "key" Key
                                                 :> (QueryParam' '[Required, Strict] "code" Value
                                                     :> Get
                                                          '[JSON] ConversationCoverView))))))))))))
      :<|> (Named
              "create-group-conversation@v2"
              (Summary "Create a new conversation"
               :> (DescriptionOAuthScope 'WriteConversations
                   :> (MakesFederatedCall 'Brig "api-version"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (Until 'V3
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'MLSNonEmptyMemberList
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow
                                                                     UnreachableBackendsLegacy
                                                                   :> (Description
                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                       :> (ZLocalUser
                                                                           :> (ZOptConn
                                                                               :> ("conversations"
                                                                                   :> (VersionedReqBody
                                                                                         'V2
                                                                                         '[JSON]
                                                                                         NewConv
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   200
                                                                                                   "Conversation existed"
                                                                                                   Conversation),
                                                                                              WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   201
                                                                                                   "Conversation created"
                                                                                                   Conversation)]
                                                                                            (ResponseForExistedCreated
                                                                                               Conversation))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation@v3"
                    (Summary "Create a new conversation"
                     :> (DescriptionOAuthScope 'WriteConversations
                         :> (MakesFederatedCall 'Brig "api-version"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V3
                                         :> (Until 'V4
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSNonEmptyMemberList
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow
                                                                           'MissingLegalholdConsent
                                                                         :> (CanThrow
                                                                               UnreachableBackendsLegacy
                                                                             :> (Description
                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZOptConn
                                                                                         :> ("conversations"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   NewConv
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V3
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V3
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             Conversation)]
                                                                                                      (ResponseForExistedCreated
                                                                                                         Conversation)))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation@v5"
                          (Summary "Create a new conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V4
                                               :> (Until 'V6
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSNonEmptyMemberList
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'MissingLegalholdConsent
                                                                               :> (CanThrow
                                                                                     NonFederatingBackends
                                                                                   :> (CanThrow
                                                                                         UnreachableBackends
                                                                                       :> (Description
                                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             NewConv
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    CreateGroupConversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V5
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       CreateGroupConversation)]
                                                                                                                CreateGroupConversationResponse)))))))))))))))))))))
                        :<|> (Named
                                "create-group-conversation"
                                (Summary "Create a new conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (From 'V6
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'MLSNonEmptyMemberList
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (Description
                                                                                               "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZOptConn
                                                                                                     :> ("conversations"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               NewConv
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      Conversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         200
                                                                                                                         "Conversation existed"
                                                                                                                         Conversation),
                                                                                                                    WithHeaders
                                                                                                                      ConversationHeaders
                                                                                                                      CreateGroupConversation
                                                                                                                      (VersionedRespond
                                                                                                                         'V6
                                                                                                                         201
                                                                                                                         "Conversation created"
                                                                                                                         CreateGroupConversation)]
                                                                                                                  CreateGroupConversationResponse))))))))))))))))))))
                              :<|> (Named
                                      "create-self-conversation@v2"
                                      (Summary "Create a self-conversation"
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("self"
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V2
                                                                   200
                                                                   "Conversation existed"
                                                                   Conversation),
                                                              WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V2
                                                                   201
                                                                   "Conversation created"
                                                                   Conversation)]
                                                            (ResponseForExistedCreated
                                                               Conversation))))))
                                    :<|> (Named
                                            "create-self-conversation@v5"
                                            (Summary "Create a self-conversation"
                                             :> (From 'V3
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("self"
                                                                 :> MultiVerb
                                                                      'POST
                                                                      '[JSON]
                                                                      '[WithHeaders
                                                                          ConversationHeaders
                                                                          Conversation
                                                                          (VersionedRespond
                                                                             'V5
                                                                             200
                                                                             "Conversation existed"
                                                                             Conversation),
                                                                        WithHeaders
                                                                          ConversationHeaders
                                                                          Conversation
                                                                          (VersionedRespond
                                                                             'V5
                                                                             201
                                                                             "Conversation created"
                                                                             Conversation)]
                                                                      (ResponseForExistedCreated
                                                                         Conversation)))))))
                                          :<|> (Named
                                                  "create-self-conversation"
                                                  (Summary "Create a self-conversation"
                                                   :> (From 'V6
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("self"
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V6
                                                                               200
                                                                               "Conversation existed"
                                                                               Conversation),
                                                                          WithHeaders
                                                                            ConversationHeaders
                                                                            Conversation
                                                                            (VersionedRespond
                                                                               'V6
                                                                               201
                                                                               "Conversation created"
                                                                               Conversation)]
                                                                        (ResponseForExistedCreated
                                                                           Conversation))))))
                                                :<|> (Named
                                                        "get-mls-self-conversation@v5"
                                                        (Summary
                                                           "Get the user's MLS self-conversation"
                                                         :> (From 'V5
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> ("mls-self"
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[VersionedRespond
                                                                                          'V5
                                                                                          200
                                                                                          "The MLS self-conversation"
                                                                                          Conversation]
                                                                                      Conversation)))))))
                                                      :<|> (Named
                                                              "get-mls-self-conversation"
                                                              (Summary
                                                                 "Get the user's MLS self-conversation"
                                                               :> (From 'V6
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> ("mls-self"
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "The MLS self-conversation"
                                                                                            Conversation]
                                                                                        Conversation))))))
                                                            :<|> (Named
                                                                    "get-subconversation"
                                                                    (Summary
                                                                       "Get information about an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "get-sub-conversation"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'MLSSubConvUnsupportedConvType
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("subconversations"
                                                                                                         :> (Capture
                                                                                                               "subconv"
                                                                                                               SubConvId
                                                                                                             :> MultiVerb
                                                                                                                  'GET
                                                                                                                  '[JSON]
                                                                                                                  '[Respond
                                                                                                                      200
                                                                                                                      "Subconversation"
                                                                                                                      PublicSubConversation]
                                                                                                                  PublicSubConversation)))))))))))
                                                                  :<|> (Named
                                                                          "leave-subconversation"
                                                                          (Summary
                                                                             "Leave an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "leave-sub-conversation"
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'MLSProtocolErrorTag
                                                                                                   :> (CanThrow
                                                                                                         'MLSStaleMessage
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZClient
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("subconversations"
                                                                                                                               :> (Capture
                                                                                                                                     "subconv"
                                                                                                                                     SubConvId
                                                                                                                                   :> ("self"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'DELETE
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "OK"]
                                                                                                                                            ()))))))))))))))))
                                                                        :<|> (Named
                                                                                "delete-subconversation"
                                                                                (Summary
                                                                                   "Delete an MLS subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "delete-sub-conversation"
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (CanThrow
                                                                                                           'MLSStaleMessage
                                                                                                         :> (ZLocalUser
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("subconversations"
                                                                                                                         :> (Capture
                                                                                                                               "subconv"
                                                                                                                               SubConvId
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   DeleteSubConversationRequest
                                                                                                                                 :> MultiVerb
                                                                                                                                      'DELETE
                                                                                                                                      '[JSON]
                                                                                                                                      '[Respond
                                                                                                                                          200
                                                                                                                                          "Deletion successful"
                                                                                                                                          ()]
                                                                                                                                      ())))))))))))))
                                                                              :<|> (Named
                                                                                      "get-subconversation-group-info"
                                                                                      (Summary
                                                                                         "Get MLS group information of subconversation"
                                                                                       :> (From 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "query-group-info"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'MLSMissingGroupInfo
                                                                                                       :> (CanThrow
                                                                                                             'MLSNotEnabled
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("subconversations"
                                                                                                                           :> (Capture
                                                                                                                                 "subconv"
                                                                                                                                 SubConvId
                                                                                                                               :> ("groupinfo"
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[MLS]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "The group information"
                                                                                                                                            GroupInfoData]
                                                                                                                                        GroupInfoData))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-one-to-one-conversation@v2"
                                                                                            (Summary
                                                                                               "Create a 1:1 conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "api-version"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-created"
                                                                                                     :> (Until
                                                                                                           'V3
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NoBindingTeamMembers
                                                                                                                     :> (CanThrow
                                                                                                                           'NonBindingTeam
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotConnected
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("one2one"
                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                       'V2
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       NewConv
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 200
                                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                                 Conversation),
                                                                                                                                                                            WithHeaders
                                                                                                                                                                              ConversationHeaders
                                                                                                                                                                              Conversation
                                                                                                                                                                              (VersionedRespond
                                                                                                                                                                                 'V2
                                                                                                                                                                                 201
                                                                                                                                                                                 "Conversation created"
                                                                                                                                                                                 Conversation)]
                                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                                             Conversation))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-one-to-one-conversation"
                                                                                                  (Summary
                                                                                                     "Create a 1:1 conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-created"
                                                                                                       :> (From
                                                                                                             'V3
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'NoBindingTeamMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'NonBindingTeam
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                               :> (CanThrow
                                                                                                                                                     UnreachableBackendsLegacy
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> ("one2one"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         NewConv
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V3
                                                                                                                                                                                   200
                                                                                                                                                                                   "Conversation existed"
                                                                                                                                                                                   Conversation),
                                                                                                                                                                              WithHeaders
                                                                                                                                                                                ConversationHeaders
                                                                                                                                                                                Conversation
                                                                                                                                                                                (VersionedRespond
                                                                                                                                                                                   'V3
                                                                                                                                                                                   201
                                                                                                                                                                                   "Conversation created"
                                                                                                                                                                                   Conversation)]
                                                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                                                               Conversation)))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation@v5"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V5
                                                                                                             :> (Until
                                                                                                                   'V6
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNotEnabled
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("one2one"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "usr"
                                                                                                                                               UserId
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[VersionedRespond
                                                                                                                                                      'V5
                                                                                                                                                      200
                                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                                      Conversation]
                                                                                                                                                  Conversation))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation@v6"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V6
                                                                                                                   :> (Until
                                                                                                                         'V7
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'MLSNotEnabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("one2one"
                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                 "usr"
                                                                                                                                                 UserId
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                           MLSPublicKey)]
                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                       MLSPublicKey))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-one-to-one-mls-conversation"
                                                                                                                    (Summary
                                                                                                                       "Get an MLS 1:1 conversation"
                                                                                                                     :> (From
                                                                                                                           'V7
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (CanThrow
                                                                                                                                   'MLSNotEnabled
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotConnected
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> ("one2one"
                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> (QueryParam
                                                                                                                                                       "format"
                                                                                                                                                       MLSPublicKeyFormat
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'GET
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[Respond
                                                                                                                                                              200
                                                                                                                                                              "MLS 1-1 conversation"
                                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                                 SomeKey)]
                                                                                                                                                          (MLSOne2OneConversation
                                                                                                                                                             SomeKey))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Add members to an existing conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (Until
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             Invite
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation-unqualified2"
                                                                                                                                (Summary
                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (Until
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> ("v2"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "add-members-to-conversation"
                                                                                                                                      (Summary
                                                                                                                                         "Add qualified members to an existing conversation."
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (From
                                                                                                                                                     'V2
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'AddConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'LeaveConversation)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'TooManyMembers
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'NotConnected
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             NonFederatingBackends
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 UnreachableBackends
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "join-conversation-by-id-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                             :> (Until
                                                                                                                                                   'V5
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("join"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Join a conversation using a reusable code"
                                                                                                                                                   :> (Description
                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CodeNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'TooManyMembers
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> ("join"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "code-check"
                                                                                                                                                        (Summary
                                                                                                                                                           "Check validity of a conversation code."
                                                                                                                                                         :> (Description
                                                                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'CodeNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidConversationPassword
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> ("code-check"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationCode
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Valid"]
                                                                                                                                                                                          ()))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V4
                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Create or recreate a conversation code"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V4
                                                                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                                                                               'WriteConversationsCode
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZOptConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-code-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Delete conversation code"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'DELETE
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                                                                      Event]
                                                                                                                                                                                                                  Event))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-code"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get existing conversation code"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'CodeNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'GET
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "member-typing-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                                          ())))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'POST
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "remove-member"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-other-member"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-group-conversation@v2" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "galley" "on-conversation-created",
   (HasAnnotation 'Remote "galley" "on-conversation-updated",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> Dict (HasAnnotation 'Remote "brig" "api-version")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'MLSNonEmptyMemberList ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error UnreachableBackendsLegacy) r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member TeamStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem r (ConversationResponse Conversation)
createGroupConversationUpToV3))
    API
  (Named
     "create-group-conversation@v2"
     (Summary "Create a new conversation"
      :> (DescriptionOAuthScope 'WriteConversations
          :> (MakesFederatedCall 'Brig "api-version"
              :> (MakesFederatedCall 'Galley "on-conversation-created"
                  :> (MakesFederatedCall 'Galley "on-conversation-updated"
                      :> (Until 'V3
                          :> (CanThrow 'ConvAccessDenied
                              :> (CanThrow 'MLSNonEmptyMemberList
                                  :> (CanThrow 'MLSNotEnabled
                                      :> (CanThrow 'NotConnected
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow UnreachableBackendsLegacy
                                                          :> (Description
                                                                "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                              :> (ZLocalUser
                                                                  :> (ZOptConn
                                                                      :> ("conversations"
                                                                          :> (VersionedReqBody
                                                                                'V2 '[JSON] NewConv
                                                                              :> MultiVerb
                                                                                   'POST
                                                                                   '[JSON]
                                                                                   '[WithHeaders
                                                                                       ConversationHeaders
                                                                                       Conversation
                                                                                       (VersionedRespond
                                                                                          'V2
                                                                                          200
                                                                                          "Conversation existed"
                                                                                          Conversation),
                                                                                     WithHeaders
                                                                                       ConversationHeaders
                                                                                       Conversation
                                                                                       (VersionedRespond
                                                                                          'V2
                                                                                          201
                                                                                          "Conversation created"
                                                                                          Conversation)]
                                                                                   (ResponseForExistedCreated
                                                                                      Conversation)))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-group-conversation@v3"
        (Summary "Create a new conversation"
         :> (DescriptionOAuthScope 'WriteConversations
             :> (MakesFederatedCall 'Brig "api-version"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V3
                             :> (Until 'V4
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSNonEmptyMemberList
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'MissingLegalholdConsent
                                                             :> (CanThrow UnreachableBackendsLegacy
                                                                 :> (Description
                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                     :> (ZLocalUser
                                                                         :> (ZOptConn
                                                                             :> ("conversations"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       NewConv
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V3
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V3
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation)))))))))))))))))))))
      :<|> (Named
              "create-group-conversation@v5"
              (Summary "Create a new conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V4
                                   :> (Until 'V6
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSNonEmptyMemberList
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'MissingLegalholdConsent
                                                                   :> (CanThrow
                                                                         NonFederatingBackends
                                                                       :> (CanThrow
                                                                             UnreachableBackends
                                                                           :> (Description
                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                               :> (ZLocalUser
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewConv
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        CreateGroupConversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           CreateGroupConversation)]
                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation"
                    (Summary "Create a new conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V6
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (Description
                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZOptConn
                                                                                         :> ("conversations"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   NewConv
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          CreateGroupConversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             CreateGroupConversation)]
                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                  :<|> (Named
                          "create-self-conversation@v2"
                          (Summary "Create a self-conversation"
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("self"
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V2 200 "Conversation existed" Conversation),
                                                  WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V2 201 "Conversation created" Conversation)]
                                                (ResponseForExistedCreated Conversation))))))
                        :<|> (Named
                                "create-self-conversation@v5"
                                (Summary "Create a self-conversation"
                                 :> (From 'V3
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("self"
                                                     :> MultiVerb
                                                          'POST
                                                          '[JSON]
                                                          '[WithHeaders
                                                              ConversationHeaders
                                                              Conversation
                                                              (VersionedRespond
                                                                 'V5
                                                                 200
                                                                 "Conversation existed"
                                                                 Conversation),
                                                            WithHeaders
                                                              ConversationHeaders
                                                              Conversation
                                                              (VersionedRespond
                                                                 'V5
                                                                 201
                                                                 "Conversation created"
                                                                 Conversation)]
                                                          (ResponseForExistedCreated
                                                             Conversation)))))))
                              :<|> (Named
                                      "create-self-conversation"
                                      (Summary "Create a self-conversation"
                                       :> (From 'V6
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("self"
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V6
                                                                   200
                                                                   "Conversation existed"
                                                                   Conversation),
                                                              WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V6
                                                                   201
                                                                   "Conversation created"
                                                                   Conversation)]
                                                            (ResponseForExistedCreated
                                                               Conversation))))))
                                    :<|> (Named
                                            "get-mls-self-conversation@v5"
                                            (Summary "Get the user's MLS self-conversation"
                                             :> (From 'V5
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("mls-self"
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[VersionedRespond
                                                                              'V5
                                                                              200
                                                                              "The MLS self-conversation"
                                                                              Conversation]
                                                                          Conversation)))))))
                                          :<|> (Named
                                                  "get-mls-self-conversation"
                                                  (Summary "Get the user's MLS self-conversation"
                                                   :> (From 'V6
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("mls-self"
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "The MLS self-conversation"
                                                                                Conversation]
                                                                            Conversation))))))
                                                :<|> (Named
                                                        "get-subconversation"
                                                        (Summary
                                                           "Get information about an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "get-sub-conversation"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSSubConvUnsupportedConvType
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("subconversations"
                                                                                             :> (Capture
                                                                                                   "subconv"
                                                                                                   SubConvId
                                                                                                 :> MultiVerb
                                                                                                      'GET
                                                                                                      '[JSON]
                                                                                                      '[Respond
                                                                                                          200
                                                                                                          "Subconversation"
                                                                                                          PublicSubConversation]
                                                                                                      PublicSubConversation)))))))))))
                                                      :<|> (Named
                                                              "leave-subconversation"
                                                              (Summary
                                                                 "Leave an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "leave-sub-conversation"
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'MLSProtocolErrorTag
                                                                                       :> (CanThrow
                                                                                             'MLSStaleMessage
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZClient
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("subconversations"
                                                                                                                   :> (Capture
                                                                                                                         "subconv"
                                                                                                                         SubConvId
                                                                                                                       :> ("self"
                                                                                                                           :> MultiVerb
                                                                                                                                'DELETE
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "OK"]
                                                                                                                                ()))))))))))))))))
                                                            :<|> (Named
                                                                    "delete-subconversation"
                                                                    (Summary
                                                                       "Delete an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "delete-sub-conversation"
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'MLSStaleMessage
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("subconversations"
                                                                                                             :> (Capture
                                                                                                                   "subconv"
                                                                                                                   SubConvId
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       DeleteSubConversationRequest
                                                                                                                     :> MultiVerb
                                                                                                                          'DELETE
                                                                                                                          '[JSON]
                                                                                                                          '[Respond
                                                                                                                              200
                                                                                                                              "Deletion successful"
                                                                                                                              ()]
                                                                                                                          ())))))))))))))
                                                                  :<|> (Named
                                                                          "get-subconversation-group-info"
                                                                          (Summary
                                                                             "Get MLS group information of subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "query-group-info"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'MLSMissingGroupInfo
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("subconversations"
                                                                                                               :> (Capture
                                                                                                                     "subconv"
                                                                                                                     SubConvId
                                                                                                                   :> ("groupinfo"
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[MLS]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "The group information"
                                                                                                                                GroupInfoData]
                                                                                                                            GroupInfoData))))))))))))
                                                                        :<|> (Named
                                                                                "create-one-to-one-conversation@v2"
                                                                                (Summary
                                                                                   "Create a 1:1 conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-created"
                                                                                         :> (Until
                                                                                               'V3
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NoBindingTeamMembers
                                                                                                         :> (CanThrow
                                                                                                               'NonBindingTeam
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("one2one"
                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                           'V2
                                                                                                                                                           '[JSON]
                                                                                                                                                           NewConv
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     200
                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                     Conversation),
                                                                                                                                                                WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     201
                                                                                                                                                                     "Conversation created"
                                                                                                                                                                     Conversation)]
                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-one-to-one-conversation"
                                                                                      (Summary
                                                                                         "Create a 1:1 conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-created"
                                                                                           :> (From
                                                                                                 'V3
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'NoBindingTeamMembers
                                                                                                           :> (CanThrow
                                                                                                                 'NonBindingTeam
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                   :> (CanThrow
                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("one2one"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             NewConv
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V3
                                                                                                                                                                       200
                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                       Conversation),
                                                                                                                                                                  WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V3
                                                                                                                                                                       201
                                                                                                                                                                       "Conversation created"
                                                                                                                                                                       Conversation)]
                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> (CanThrow
                                                                                                               'MLSNotEnabled
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("one2one"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "usr"
                                                                                                                                   UserId
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[VersionedRespond
                                                                                                                                          'V5
                                                                                                                                          200
                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                          Conversation]
                                                                                                                                      Conversation))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (Until
                                                                                                             'V7
                                                                                                           :> (ZLocalUser
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNotEnabled
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("one2one"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "usr"
                                                                                                                                     UserId
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                               MLSPublicKey)]
                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                           MLSPublicKey))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V7
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("one2one"
                                                                                                                                 :> (QualifiedCapture
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> (QueryParam
                                                                                                                                           "format"
                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                     SomeKey)]
                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                 SomeKey))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                              (Summary
                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (Until
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 Invite
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                    (Summary
                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (Until
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation"
                                                                                                                          (Summary
                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (From
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                 :> (Until
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotATeamMember
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TooManyMembers
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("join"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                       :> (Description
                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CodeNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "code-check"
                                                                                                                                            (Summary
                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                             :> (Description
                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'CodeNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationCode
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Valid"]
                                                                                                                                                                              ()))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V4
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                           :> (ZUser
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                         :> (From
                                                                                                                                                               'V4
                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                          Event]
                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-code"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-group-conversation@v2"
        (Summary "Create a new conversation"
         :> (DescriptionOAuthScope 'WriteConversations
             :> (MakesFederatedCall 'Brig "api-version"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (Until 'V3
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'MLSNonEmptyMemberList
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow UnreachableBackendsLegacy
                                                             :> (Description
                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                 :> (ZLocalUser
                                                                     :> (ZOptConn
                                                                         :> ("conversations"
                                                                             :> (VersionedReqBody
                                                                                   'V2
                                                                                   '[JSON]
                                                                                   NewConv
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             200
                                                                                             "Conversation existed"
                                                                                             Conversation),
                                                                                        WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             201
                                                                                             "Conversation created"
                                                                                             Conversation)]
                                                                                      (ResponseForExistedCreated
                                                                                         Conversation))))))))))))))))))))
      :<|> (Named
              "create-group-conversation@v3"
              (Summary "Create a new conversation"
               :> (DescriptionOAuthScope 'WriteConversations
                   :> (MakesFederatedCall 'Brig "api-version"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V3
                                   :> (Until 'V4
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSNonEmptyMemberList
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'MissingLegalholdConsent
                                                                   :> (CanThrow
                                                                         UnreachableBackendsLegacy
                                                                       :> (Description
                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                           :> (ZLocalUser
                                                                               :> (ZOptConn
                                                                                   :> ("conversations"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             NewConv
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V3
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V3
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       Conversation)]
                                                                                                (ResponseForExistedCreated
                                                                                                   Conversation)))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation@v5"
                    (Summary "Create a new conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V4
                                         :> (Until 'V6
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSNonEmptyMemberList
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow
                                                                           'MissingLegalholdConsent
                                                                         :> (CanThrow
                                                                               NonFederatingBackends
                                                                             :> (CanThrow
                                                                                   UnreachableBackends
                                                                                 :> (Description
                                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       NewConv
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              CreateGroupConversation
                                                                                                              (VersionedRespond
                                                                                                                 'V5
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 CreateGroupConversation)]
                                                                                                          CreateGroupConversationResponse)))))))))))))))))))))
                  :<|> (Named
                          "create-group-conversation"
                          (Summary "Create a new conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (From 'V6
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'MLSNonEmptyMemberList
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (Description
                                                                                         "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZOptConn
                                                                                               :> ("conversations"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         NewConv
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                Conversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   200
                                                                                                                   "Conversation existed"
                                                                                                                   Conversation),
                                                                                                              WithHeaders
                                                                                                                ConversationHeaders
                                                                                                                CreateGroupConversation
                                                                                                                (VersionedRespond
                                                                                                                   'V6
                                                                                                                   201
                                                                                                                   "Conversation created"
                                                                                                                   CreateGroupConversation)]
                                                                                                            CreateGroupConversationResponse))))))))))))))))))))
                        :<|> (Named
                                "create-self-conversation@v2"
                                (Summary "Create a self-conversation"
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("self"
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V2
                                                             200
                                                             "Conversation existed"
                                                             Conversation),
                                                        WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V2
                                                             201
                                                             "Conversation created"
                                                             Conversation)]
                                                      (ResponseForExistedCreated Conversation))))))
                              :<|> (Named
                                      "create-self-conversation@v5"
                                      (Summary "Create a self-conversation"
                                       :> (From 'V3
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("self"
                                                           :> MultiVerb
                                                                'POST
                                                                '[JSON]
                                                                '[WithHeaders
                                                                    ConversationHeaders
                                                                    Conversation
                                                                    (VersionedRespond
                                                                       'V5
                                                                       200
                                                                       "Conversation existed"
                                                                       Conversation),
                                                                  WithHeaders
                                                                    ConversationHeaders
                                                                    Conversation
                                                                    (VersionedRespond
                                                                       'V5
                                                                       201
                                                                       "Conversation created"
                                                                       Conversation)]
                                                                (ResponseForExistedCreated
                                                                   Conversation)))))))
                                    :<|> (Named
                                            "create-self-conversation"
                                            (Summary "Create a self-conversation"
                                             :> (From 'V6
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("self"
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V6
                                                                         200
                                                                         "Conversation existed"
                                                                         Conversation),
                                                                    WithHeaders
                                                                      ConversationHeaders
                                                                      Conversation
                                                                      (VersionedRespond
                                                                         'V6
                                                                         201
                                                                         "Conversation created"
                                                                         Conversation)]
                                                                  (ResponseForExistedCreated
                                                                     Conversation))))))
                                          :<|> (Named
                                                  "get-mls-self-conversation@v5"
                                                  (Summary "Get the user's MLS self-conversation"
                                                   :> (From 'V5
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> ("mls-self"
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[VersionedRespond
                                                                                    'V5
                                                                                    200
                                                                                    "The MLS self-conversation"
                                                                                    Conversation]
                                                                                Conversation)))))))
                                                :<|> (Named
                                                        "get-mls-self-conversation"
                                                        (Summary
                                                           "Get the user's MLS self-conversation"
                                                         :> (From 'V6
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> ("mls-self"
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "The MLS self-conversation"
                                                                                      Conversation]
                                                                                  Conversation))))))
                                                      :<|> (Named
                                                              "get-subconversation"
                                                              (Summary
                                                                 "Get information about an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "get-sub-conversation"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'MLSSubConvUnsupportedConvType
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("subconversations"
                                                                                                   :> (Capture
                                                                                                         "subconv"
                                                                                                         SubConvId
                                                                                                       :> MultiVerb
                                                                                                            'GET
                                                                                                            '[JSON]
                                                                                                            '[Respond
                                                                                                                200
                                                                                                                "Subconversation"
                                                                                                                PublicSubConversation]
                                                                                                            PublicSubConversation)))))))))))
                                                            :<|> (Named
                                                                    "leave-subconversation"
                                                                    (Summary
                                                                       "Leave an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "leave-sub-conversation"
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'MLSProtocolErrorTag
                                                                                             :> (CanThrow
                                                                                                   'MLSStaleMessage
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZClient
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("subconversations"
                                                                                                                         :> (Capture
                                                                                                                               "subconv"
                                                                                                                               SubConvId
                                                                                                                             :> ("self"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'DELETE
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "OK"]
                                                                                                                                      ()))))))))))))))))
                                                                  :<|> (Named
                                                                          "delete-subconversation"
                                                                          (Summary
                                                                             "Delete an MLS subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "delete-sub-conversation"
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (CanThrow
                                                                                                     'MLSStaleMessage
                                                                                                   :> (ZLocalUser
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("subconversations"
                                                                                                                   :> (Capture
                                                                                                                         "subconv"
                                                                                                                         SubConvId
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             DeleteSubConversationRequest
                                                                                                                           :> MultiVerb
                                                                                                                                'DELETE
                                                                                                                                '[JSON]
                                                                                                                                '[Respond
                                                                                                                                    200
                                                                                                                                    "Deletion successful"
                                                                                                                                    ()]
                                                                                                                                ())))))))))))))
                                                                        :<|> (Named
                                                                                "get-subconversation-group-info"
                                                                                (Summary
                                                                                   "Get MLS group information of subconversation"
                                                                                 :> (From 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "query-group-info"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'MLSMissingGroupInfo
                                                                                                 :> (CanThrow
                                                                                                       'MLSNotEnabled
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("subconversations"
                                                                                                                     :> (Capture
                                                                                                                           "subconv"
                                                                                                                           SubConvId
                                                                                                                         :> ("groupinfo"
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[MLS]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "The group information"
                                                                                                                                      GroupInfoData]
                                                                                                                                  GroupInfoData))))))))))))
                                                                              :<|> (Named
                                                                                      "create-one-to-one-conversation@v2"
                                                                                      (Summary
                                                                                         "Create a 1:1 conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "api-version"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-created"
                                                                                               :> (Until
                                                                                                     'V3
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NoBindingTeamMembers
                                                                                                               :> (CanThrow
                                                                                                                     'NonBindingTeam
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'NotConnected
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             UnreachableBackendsLegacy
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("one2one"
                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                 'V2
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 NewConv
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           200
                                                                                                                                                                           "Conversation existed"
                                                                                                                                                                           Conversation),
                                                                                                                                                                      WithHeaders
                                                                                                                                                                        ConversationHeaders
                                                                                                                                                                        Conversation
                                                                                                                                                                        (VersionedRespond
                                                                                                                                                                           'V2
                                                                                                                                                                           201
                                                                                                                                                                           "Conversation created"
                                                                                                                                                                           Conversation)]
                                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                                       Conversation))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-one-to-one-conversation"
                                                                                            (Summary
                                                                                               "Create a 1:1 conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-created"
                                                                                                 :> (From
                                                                                                       'V3
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'NoBindingTeamMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'NonBindingTeam
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                         :> (CanThrow
                                                                                                                                               UnreachableBackendsLegacy
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> ("one2one"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   NewConv
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V3
                                                                                                                                                                             200
                                                                                                                                                                             "Conversation existed"
                                                                                                                                                                             Conversation),
                                                                                                                                                                        WithHeaders
                                                                                                                                                                          ConversationHeaders
                                                                                                                                                                          Conversation
                                                                                                                                                                          (VersionedRespond
                                                                                                                                                                             'V3
                                                                                                                                                                             201
                                                                                                                                                                             "Conversation created"
                                                                                                                                                                             Conversation)]
                                                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                                                         Conversation)))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation@v5"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V5
                                                                                                       :> (Until
                                                                                                             'V6
                                                                                                           :> (ZLocalUser
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNotEnabled
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSFederatedOne2OneNotSupported
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("one2one"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "usr"
                                                                                                                                         UserId
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[VersionedRespond
                                                                                                                                                'V5
                                                                                                                                                200
                                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                                Conversation]
                                                                                                                                            Conversation))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation@v6"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V6
                                                                                                             :> (Until
                                                                                                                   'V7
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (CanThrow
                                                                                                                           'MLSNotEnabled
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("one2one"
                                                                                                                                     :> (QualifiedCapture
                                                                                                                                           "usr"
                                                                                                                                           UserId
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                     MLSPublicKey)]
                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                 MLSPublicKey))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-one-to-one-mls-conversation"
                                                                                                              (Summary
                                                                                                                 "Get an MLS 1:1 conversation"
                                                                                                               :> (From
                                                                                                                     'V7
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (CanThrow
                                                                                                                             'MLSNotEnabled
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotConnected
                                                                                                                               :> ("conversations"
                                                                                                                                   :> ("one2one"
                                                                                                                                       :> (QualifiedCapture
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> (QueryParam
                                                                                                                                                 "format"
                                                                                                                                                 MLSPublicKeyFormat
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'GET
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[Respond
                                                                                                                                                        200
                                                                                                                                                        "MLS 1-1 conversation"
                                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                                           SomeKey)]
                                                                                                                                                    (MLSOne2OneConversation
                                                                                                                                                       SomeKey))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Add members to an existing conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (Until
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       Invite
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation-unqualified2"
                                                                                                                          (Summary
                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (Until
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> ("v2"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "add-members-to-conversation"
                                                                                                                                (Summary
                                                                                                                                   "Add qualified members to an existing conversation."
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (From
                                                                                                                                               'V2
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'AddConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'LeaveConversation)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'TooManyMembers
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'NotConnected
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       NonFederatingBackends
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           UnreachableBackends
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "join-conversation-by-id-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                       :> (Until
                                                                                                                                             'V5
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotATeamMember
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("join"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "join-conversation-by-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Join a conversation using a reusable code"
                                                                                                                                             :> (Description
                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CodeNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'TooManyMembers
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> ("join"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           JoinConversationByCode
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvJoinResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "code-check"
                                                                                                                                                  (Summary
                                                                                                                                                     "Check validity of a conversation code."
                                                                                                                                                   :> (Description
                                                                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'CodeNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidConversationPassword
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> ("code-check"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationCode
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Valid"]
                                                                                                                                                                                    ()))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V4
                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "create-conversation-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Create or recreate a conversation code"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V4
                                                                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                                                                         'WriteConversationsCode
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZOptConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-code-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Delete conversation code"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'DELETE
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                                                                Event]
                                                                                                                                                                                                            Event))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-code"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get existing conversation code"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'CodeNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'GET
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[Respond
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "member-typing-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                                    ())))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "member-typing-qualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Sending typing notifications"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'POST
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "remove-member"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "leave-conversation"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-other-member"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-group-conversation@v3" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "galley" "on-conversation-created",
   (HasAnnotation 'Remote "galley" "on-conversation-updated",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> Dict (HasAnnotation 'Remote "brig" "api-version")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'MLSNonEmptyMemberList ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error UnreachableBackendsLegacy) r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member TeamStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem r (ConversationResponse Conversation)
createGroupConversationUpToV3))
    API
  (Named
     "create-group-conversation@v3"
     (Summary "Create a new conversation"
      :> (DescriptionOAuthScope 'WriteConversations
          :> (MakesFederatedCall 'Brig "api-version"
              :> (MakesFederatedCall 'Galley "on-conversation-created"
                  :> (MakesFederatedCall 'Galley "on-conversation-updated"
                      :> (From 'V3
                          :> (Until 'V4
                              :> (CanThrow 'ConvAccessDenied
                                  :> (CanThrow 'MLSNonEmptyMemberList
                                      :> (CanThrow 'MLSNotEnabled
                                          :> (CanThrow 'NotConnected
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'MissingLegalholdConsent
                                                          :> (CanThrow UnreachableBackendsLegacy
                                                              :> (Description
                                                                    "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                  :> (ZLocalUser
                                                                      :> (ZOptConn
                                                                          :> ("conversations"
                                                                              :> (ReqBody
                                                                                    '[JSON] NewConv
                                                                                  :> MultiVerb
                                                                                       'POST
                                                                                       '[JSON]
                                                                                       '[WithHeaders
                                                                                           ConversationHeaders
                                                                                           Conversation
                                                                                           (VersionedRespond
                                                                                              'V3
                                                                                              200
                                                                                              "Conversation existed"
                                                                                              Conversation),
                                                                                         WithHeaders
                                                                                           ConversationHeaders
                                                                                           Conversation
                                                                                           (VersionedRespond
                                                                                              'V3
                                                                                              201
                                                                                              "Conversation created"
                                                                                              Conversation)]
                                                                                       (ResponseForExistedCreated
                                                                                          Conversation))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-group-conversation@v5"
        (Summary "Create a new conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V4
                             :> (Until 'V6
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSNonEmptyMemberList
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'MissingLegalholdConsent
                                                             :> (CanThrow NonFederatingBackends
                                                                 :> (CanThrow UnreachableBackends
                                                                     :> (Description
                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                         :> (ZLocalUser
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewConv
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  CreateGroupConversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     CreateGroupConversation)]
                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
      :<|> (Named
              "create-group-conversation"
              (Summary "Create a new conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V6
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'MLSNonEmptyMemberList
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (Description
                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                           :> (ZLocalUser
                                                                               :> (ZOptConn
                                                                                   :> ("conversations"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             NewConv
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    CreateGroupConversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       CreateGroupConversation)]
                                                                                                CreateGroupConversationResponse))))))))))))))))))))
            :<|> (Named
                    "create-self-conversation@v2"
                    (Summary "Create a self-conversation"
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("self"
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V2 200 "Conversation existed" Conversation),
                                            WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V2 201 "Conversation created" Conversation)]
                                          (ResponseForExistedCreated Conversation))))))
                  :<|> (Named
                          "create-self-conversation@v5"
                          (Summary "Create a self-conversation"
                           :> (From 'V3
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("self"
                                               :> MultiVerb
                                                    'POST
                                                    '[JSON]
                                                    '[WithHeaders
                                                        ConversationHeaders
                                                        Conversation
                                                        (VersionedRespond
                                                           'V5
                                                           200
                                                           "Conversation existed"
                                                           Conversation),
                                                      WithHeaders
                                                        ConversationHeaders
                                                        Conversation
                                                        (VersionedRespond
                                                           'V5
                                                           201
                                                           "Conversation created"
                                                           Conversation)]
                                                    (ResponseForExistedCreated Conversation)))))))
                        :<|> (Named
                                "create-self-conversation"
                                (Summary "Create a self-conversation"
                                 :> (From 'V6
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("self"
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V6
                                                             200
                                                             "Conversation existed"
                                                             Conversation),
                                                        WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V6
                                                             201
                                                             "Conversation created"
                                                             Conversation)]
                                                      (ResponseForExistedCreated Conversation))))))
                              :<|> (Named
                                      "get-mls-self-conversation@v5"
                                      (Summary "Get the user's MLS self-conversation"
                                       :> (From 'V5
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("mls-self"
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[VersionedRespond
                                                                        'V5
                                                                        200
                                                                        "The MLS self-conversation"
                                                                        Conversation]
                                                                    Conversation)))))))
                                    :<|> (Named
                                            "get-mls-self-conversation"
                                            (Summary "Get the user's MLS self-conversation"
                                             :> (From 'V6
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("mls-self"
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "The MLS self-conversation"
                                                                          Conversation]
                                                                      Conversation))))))
                                          :<|> (Named
                                                  "get-subconversation"
                                                  (Summary
                                                     "Get information about an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "get-sub-conversation"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSSubConvUnsupportedConvType
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture
                                                                                     "cnv" ConvId
                                                                                   :> ("subconversations"
                                                                                       :> (Capture
                                                                                             "subconv"
                                                                                             SubConvId
                                                                                           :> MultiVerb
                                                                                                'GET
                                                                                                '[JSON]
                                                                                                '[Respond
                                                                                                    200
                                                                                                    "Subconversation"
                                                                                                    PublicSubConversation]
                                                                                                PublicSubConversation)))))))))))
                                                :<|> (Named
                                                        "leave-subconversation"
                                                        (Summary "Leave an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "leave-sub-conversation"
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'MLSProtocolErrorTag
                                                                                 :> (CanThrow
                                                                                       'MLSStaleMessage
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (ZLocalUser
                                                                                             :> (ZClient
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("subconversations"
                                                                                                             :> (Capture
                                                                                                                   "subconv"
                                                                                                                   SubConvId
                                                                                                                 :> ("self"
                                                                                                                     :> MultiVerb
                                                                                                                          'DELETE
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "OK"]
                                                                                                                          ()))))))))))))))))
                                                      :<|> (Named
                                                              "delete-subconversation"
                                                              (Summary
                                                                 "Delete an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "delete-sub-conversation"
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'MLSStaleMessage
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("subconversations"
                                                                                                       :> (Capture
                                                                                                             "subconv"
                                                                                                             SubConvId
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 DeleteSubConversationRequest
                                                                                                               :> MultiVerb
                                                                                                                    'DELETE
                                                                                                                    '[JSON]
                                                                                                                    '[Respond
                                                                                                                        200
                                                                                                                        "Deletion successful"
                                                                                                                        ()]
                                                                                                                    ())))))))))))))
                                                            :<|> (Named
                                                                    "get-subconversation-group-info"
                                                                    (Summary
                                                                       "Get MLS group information of subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "query-group-info"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'MLSMissingGroupInfo
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("subconversations"
                                                                                                         :> (Capture
                                                                                                               "subconv"
                                                                                                               SubConvId
                                                                                                             :> ("groupinfo"
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[MLS]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "The group information"
                                                                                                                          GroupInfoData]
                                                                                                                      GroupInfoData))))))))))))
                                                                  :<|> (Named
                                                                          "create-one-to-one-conversation@v2"
                                                                          (Summary
                                                                             "Create a 1:1 conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-created"
                                                                                   :> (Until 'V3
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NoBindingTeamMembers
                                                                                                   :> (CanThrow
                                                                                                         'NonBindingTeam
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("one2one"
                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                     'V2
                                                                                                                                                     '[JSON]
                                                                                                                                                     NewConv
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               200
                                                                                                                                                               "Conversation existed"
                                                                                                                                                               Conversation),
                                                                                                                                                          WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               201
                                                                                                                                                               "Conversation created"
                                                                                                                                                               Conversation)]
                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                           Conversation))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-one-to-one-conversation"
                                                                                (Summary
                                                                                   "Create a 1:1 conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-created"
                                                                                     :> (From 'V3
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'NoBindingTeamMembers
                                                                                                     :> (CanThrow
                                                                                                           'NonBindingTeam
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'MissingLegalholdConsent
                                                                                                                             :> (CanThrow
                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("one2one"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       NewConv
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V3
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V3
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 Conversation)]
                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                             Conversation)))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V5
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> (CanThrow
                                                                                                         'MLSNotEnabled
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                               :> ("conversations"
                                                                                                                   :> ("one2one"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "usr"
                                                                                                                             UserId
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[VersionedRespond
                                                                                                                                    'V5
                                                                                                                                    200
                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                    Conversation]
                                                                                                                                Conversation))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (Until
                                                                                                       'V7
                                                                                                     :> (ZLocalUser
                                                                                                         :> (CanThrow
                                                                                                               'MLSNotEnabled
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("one2one"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "usr"
                                                                                                                               UserId
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                         MLSPublicKey)]
                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                     MLSPublicKey))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V7
                                                                                                       :> (ZLocalUser
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("one2one"
                                                                                                                           :> (QualifiedCapture
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> (QueryParam
                                                                                                                                     "format"
                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                               SomeKey)]
                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                           SomeKey))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                        (Summary
                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (Until
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           Invite
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                              (Summary
                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (Until
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation"
                                                                                                                    (Summary
                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (From
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                           :> (Until
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TooManyMembers
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("join"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                 :> (Description
                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CodeNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "code-check"
                                                                                                                                      (Summary
                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                       :> (Description
                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'CodeNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> ("code-check"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationCode
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Valid"]
                                                                                                                                                                        ()))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                            (Summary
                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                             :> (Until
                                                                                                                                                   'V4
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                     :> (ZUser
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                   :> (From
                                                                                                                                                         'V4
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                           :> (ZUser
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                    Event]
                                                                                                                                                                                                Event))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-code"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'GET
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                             'V2
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-group-conversation@v3"
        (Summary "Create a new conversation"
         :> (DescriptionOAuthScope 'WriteConversations
             :> (MakesFederatedCall 'Brig "api-version"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V3
                             :> (Until 'V4
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSNonEmptyMemberList
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'MissingLegalholdConsent
                                                             :> (CanThrow UnreachableBackendsLegacy
                                                                 :> (Description
                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                     :> (ZLocalUser
                                                                         :> (ZOptConn
                                                                             :> ("conversations"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       NewConv
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V3
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V3
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 Conversation)]
                                                                                          (ResponseForExistedCreated
                                                                                             Conversation)))))))))))))))))))))
      :<|> (Named
              "create-group-conversation@v5"
              (Summary "Create a new conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V4
                                   :> (Until 'V6
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSNonEmptyMemberList
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'MissingLegalholdConsent
                                                                   :> (CanThrow
                                                                         NonFederatingBackends
                                                                       :> (CanThrow
                                                                             UnreachableBackends
                                                                           :> (Description
                                                                                 "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                               :> (ZLocalUser
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewConv
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        CreateGroupConversation
                                                                                                        (VersionedRespond
                                                                                                           'V5
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           CreateGroupConversation)]
                                                                                                    CreateGroupConversationResponse)))))))))))))))))))))
            :<|> (Named
                    "create-group-conversation"
                    (Summary "Create a new conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                             :> (MakesFederatedCall 'Galley "on-conversation-created"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (From 'V6
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'MLSNonEmptyMemberList
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (Description
                                                                                   "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZOptConn
                                                                                         :> ("conversations"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   NewConv
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          Conversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             200
                                                                                                             "Conversation existed"
                                                                                                             Conversation),
                                                                                                        WithHeaders
                                                                                                          ConversationHeaders
                                                                                                          CreateGroupConversation
                                                                                                          (VersionedRespond
                                                                                                             'V6
                                                                                                             201
                                                                                                             "Conversation created"
                                                                                                             CreateGroupConversation)]
                                                                                                      CreateGroupConversationResponse))))))))))))))))))))
                  :<|> (Named
                          "create-self-conversation@v2"
                          (Summary "Create a self-conversation"
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("self"
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V2 200 "Conversation existed" Conversation),
                                                  WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V2 201 "Conversation created" Conversation)]
                                                (ResponseForExistedCreated Conversation))))))
                        :<|> (Named
                                "create-self-conversation@v5"
                                (Summary "Create a self-conversation"
                                 :> (From 'V3
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("self"
                                                     :> MultiVerb
                                                          'POST
                                                          '[JSON]
                                                          '[WithHeaders
                                                              ConversationHeaders
                                                              Conversation
                                                              (VersionedRespond
                                                                 'V5
                                                                 200
                                                                 "Conversation existed"
                                                                 Conversation),
                                                            WithHeaders
                                                              ConversationHeaders
                                                              Conversation
                                                              (VersionedRespond
                                                                 'V5
                                                                 201
                                                                 "Conversation created"
                                                                 Conversation)]
                                                          (ResponseForExistedCreated
                                                             Conversation)))))))
                              :<|> (Named
                                      "create-self-conversation"
                                      (Summary "Create a self-conversation"
                                       :> (From 'V6
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("self"
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V6
                                                                   200
                                                                   "Conversation existed"
                                                                   Conversation),
                                                              WithHeaders
                                                                ConversationHeaders
                                                                Conversation
                                                                (VersionedRespond
                                                                   'V6
                                                                   201
                                                                   "Conversation created"
                                                                   Conversation)]
                                                            (ResponseForExistedCreated
                                                               Conversation))))))
                                    :<|> (Named
                                            "get-mls-self-conversation@v5"
                                            (Summary "Get the user's MLS self-conversation"
                                             :> (From 'V5
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> ("mls-self"
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[VersionedRespond
                                                                              'V5
                                                                              200
                                                                              "The MLS self-conversation"
                                                                              Conversation]
                                                                          Conversation)))))))
                                          :<|> (Named
                                                  "get-mls-self-conversation"
                                                  (Summary "Get the user's MLS self-conversation"
                                                   :> (From 'V6
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> ("mls-self"
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "The MLS self-conversation"
                                                                                Conversation]
                                                                            Conversation))))))
                                                :<|> (Named
                                                        "get-subconversation"
                                                        (Summary
                                                           "Get information about an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "get-sub-conversation"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'MLSSubConvUnsupportedConvType
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("subconversations"
                                                                                             :> (Capture
                                                                                                   "subconv"
                                                                                                   SubConvId
                                                                                                 :> MultiVerb
                                                                                                      'GET
                                                                                                      '[JSON]
                                                                                                      '[Respond
                                                                                                          200
                                                                                                          "Subconversation"
                                                                                                          PublicSubConversation]
                                                                                                      PublicSubConversation)))))))))))
                                                      :<|> (Named
                                                              "leave-subconversation"
                                                              (Summary
                                                                 "Leave an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "leave-sub-conversation"
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'MLSProtocolErrorTag
                                                                                       :> (CanThrow
                                                                                             'MLSStaleMessage
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZClient
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("subconversations"
                                                                                                                   :> (Capture
                                                                                                                         "subconv"
                                                                                                                         SubConvId
                                                                                                                       :> ("self"
                                                                                                                           :> MultiVerb
                                                                                                                                'DELETE
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "OK"]
                                                                                                                                ()))))))))))))))))
                                                            :<|> (Named
                                                                    "delete-subconversation"
                                                                    (Summary
                                                                       "Delete an MLS subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "delete-sub-conversation"
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (CanThrow
                                                                                               'MLSStaleMessage
                                                                                             :> (ZLocalUser
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("subconversations"
                                                                                                             :> (Capture
                                                                                                                   "subconv"
                                                                                                                   SubConvId
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       DeleteSubConversationRequest
                                                                                                                     :> MultiVerb
                                                                                                                          'DELETE
                                                                                                                          '[JSON]
                                                                                                                          '[Respond
                                                                                                                              200
                                                                                                                              "Deletion successful"
                                                                                                                              ()]
                                                                                                                          ())))))))))))))
                                                                  :<|> (Named
                                                                          "get-subconversation-group-info"
                                                                          (Summary
                                                                             "Get MLS group information of subconversation"
                                                                           :> (From 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "query-group-info"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'MLSMissingGroupInfo
                                                                                           :> (CanThrow
                                                                                                 'MLSNotEnabled
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("subconversations"
                                                                                                               :> (Capture
                                                                                                                     "subconv"
                                                                                                                     SubConvId
                                                                                                                   :> ("groupinfo"
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[MLS]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "The group information"
                                                                                                                                GroupInfoData]
                                                                                                                            GroupInfoData))))))))))))
                                                                        :<|> (Named
                                                                                "create-one-to-one-conversation@v2"
                                                                                (Summary
                                                                                   "Create a 1:1 conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "api-version"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-created"
                                                                                         :> (Until
                                                                                               'V3
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NoBindingTeamMembers
                                                                                                         :> (CanThrow
                                                                                                               'NonBindingTeam
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'NotConnected
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       UnreachableBackendsLegacy
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("one2one"
                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                           'V2
                                                                                                                                                           '[JSON]
                                                                                                                                                           NewConv
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     200
                                                                                                                                                                     "Conversation existed"
                                                                                                                                                                     Conversation),
                                                                                                                                                                WithHeaders
                                                                                                                                                                  ConversationHeaders
                                                                                                                                                                  Conversation
                                                                                                                                                                  (VersionedRespond
                                                                                                                                                                     'V2
                                                                                                                                                                     201
                                                                                                                                                                     "Conversation created"
                                                                                                                                                                     Conversation)]
                                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                                 Conversation))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "create-one-to-one-conversation"
                                                                                      (Summary
                                                                                         "Create a 1:1 conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-created"
                                                                                           :> (From
                                                                                                 'V3
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'NoBindingTeamMembers
                                                                                                           :> (CanThrow
                                                                                                                 'NonBindingTeam
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                   :> (CanThrow
                                                                                                                                         UnreachableBackendsLegacy
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> ("one2one"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             NewConv
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V3
                                                                                                                                                                       200
                                                                                                                                                                       "Conversation existed"
                                                                                                                                                                       Conversation),
                                                                                                                                                                  WithHeaders
                                                                                                                                                                    ConversationHeaders
                                                                                                                                                                    Conversation
                                                                                                                                                                    (VersionedRespond
                                                                                                                                                                       'V3
                                                                                                                                                                       201
                                                                                                                                                                       "Conversation created"
                                                                                                                                                                       Conversation)]
                                                                                                                                                                (ResponseForExistedCreated
                                                                                                                                                                   Conversation)))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation@v5"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V5
                                                                                                 :> (Until
                                                                                                       'V6
                                                                                                     :> (ZLocalUser
                                                                                                         :> (CanThrow
                                                                                                               'MLSNotEnabled
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSFederatedOne2OneNotSupported
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("one2one"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "usr"
                                                                                                                                   UserId
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[VersionedRespond
                                                                                                                                          'V5
                                                                                                                                          200
                                                                                                                                          "MLS 1-1 conversation"
                                                                                                                                          Conversation]
                                                                                                                                      Conversation))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation@v6"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V6
                                                                                                       :> (Until
                                                                                                             'V7
                                                                                                           :> (ZLocalUser
                                                                                                               :> (CanThrow
                                                                                                                     'MLSNotEnabled
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("one2one"
                                                                                                                               :> (QualifiedCapture
                                                                                                                                     "usr"
                                                                                                                                     UserId
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                               MLSPublicKey)]
                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                           MLSPublicKey))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-one-to-one-mls-conversation"
                                                                                                        (Summary
                                                                                                           "Get an MLS 1:1 conversation"
                                                                                                         :> (From
                                                                                                               'V7
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (CanThrow
                                                                                                                       'MLSNotEnabled
                                                                                                                     :> (CanThrow
                                                                                                                           'NotConnected
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("one2one"
                                                                                                                                 :> (QualifiedCapture
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> (QueryParam
                                                                                                                                           "format"
                                                                                                                                           MLSPublicKeyFormat
                                                                                                                                         :> MultiVerb
                                                                                                                                              'GET
                                                                                                                                              '[JSON]
                                                                                                                                              '[Respond
                                                                                                                                                  200
                                                                                                                                                  "MLS 1-1 conversation"
                                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                                     SomeKey)]
                                                                                                                                              (MLSOne2OneConversation
                                                                                                                                                 SomeKey))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation-unqualified"
                                                                                                              (Summary
                                                                                                                 "Add members to an existing conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (Until
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 Invite
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation-unqualified2"
                                                                                                                    (Summary
                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (Until
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> ("v2"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "add-members-to-conversation"
                                                                                                                          (Summary
                                                                                                                             "Add qualified members to an existing conversation."
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (From
                                                                                                                                         'V2
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'AddConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'LeaveConversation)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'TooManyMembers
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotConnected
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'MissingLegalholdConsent
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 NonFederatingBackends
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     UnreachableBackends
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             InviteQualified
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "join-conversation-by-id-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                                 :> (Until
                                                                                                                                       'V5
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotATeamMember
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TooManyMembers
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("join"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "join-conversation-by-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Join a conversation using a reusable code"
                                                                                                                                       :> (Description
                                                                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CodeNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TooManyMembers
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> ("join"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     JoinConversationByCode
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvJoinResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "code-check"
                                                                                                                                            (Summary
                                                                                                                                               "Check validity of a conversation code."
                                                                                                                                             :> (Description
                                                                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'CodeNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidConversationPassword
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> ("code-check"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationCode
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Valid"]
                                                                                                                                                                              ()))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V4
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                           :> (ZUser
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "create-conversation-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Create or recreate a conversation code"
                                                                                                                                                         :> (From
                                                                                                                                                               'V4
                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                   'WriteConversationsCode
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZOptConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-conversation-guest-links-status"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-code-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Delete conversation code"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("code"
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'DELETE
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[Respond
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                                                                          Event]
                                                                                                                                                                                                      Event))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-code"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get existing conversation code"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'CodeNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                                                           :> (ZHostOpt
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("code"
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'GET
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[Respond
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "member-typing-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'POST
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                                              ())))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "member-typing-qualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Sending typing notifications"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'POST
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-member-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "remove-member"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "leave-conversation"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-other-member"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-group-conversation@v5" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "brig" "get-not-fully-connected-backends",
   (HasAnnotation 'Remote "galley" "on-conversation-created",
    (HasAnnotation 'Remote "galley" "on-conversation-updated",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      CreateGroupConversationResponse)
-> Dict (HasAnnotation 'Remote "brig" "api-version")
-> Dict
     (HasAnnotation 'Remote "brig" "get-not-fully-connected-backends")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      CreateGroupConversationResponse)
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error NonFederatingBackends) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'MLSNonEmptyMemberList ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error UnreachableBackends) r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input Env) r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member LegalHoldStore r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> NewConv -> Sem r CreateGroupConversationResponse
createGroupConversation))
    API
  (Named
     "create-group-conversation@v5"
     (Summary "Create a new conversation"
      :> (MakesFederatedCall 'Brig "api-version"
          :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
              :> (MakesFederatedCall 'Galley "on-conversation-created"
                  :> (MakesFederatedCall 'Galley "on-conversation-updated"
                      :> (From 'V4
                          :> (Until 'V6
                              :> (CanThrow 'ConvAccessDenied
                                  :> (CanThrow 'MLSNonEmptyMemberList
                                      :> (CanThrow 'MLSNotEnabled
                                          :> (CanThrow 'NotConnected
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'MissingLegalholdConsent
                                                          :> (CanThrow NonFederatingBackends
                                                              :> (CanThrow UnreachableBackends
                                                                  :> (Description
                                                                        "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                      :> (ZLocalUser
                                                                          :> (ZOptConn
                                                                              :> ("conversations"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        NewConv
                                                                                      :> MultiVerb
                                                                                           'POST
                                                                                           '[JSON]
                                                                                           '[WithHeaders
                                                                                               ConversationHeaders
                                                                                               Conversation
                                                                                               (VersionedRespond
                                                                                                  'V5
                                                                                                  200
                                                                                                  "Conversation existed"
                                                                                                  Conversation),
                                                                                             WithHeaders
                                                                                               ConversationHeaders
                                                                                               CreateGroupConversation
                                                                                               (VersionedRespond
                                                                                                  'V5
                                                                                                  201
                                                                                                  "Conversation created"
                                                                                                  CreateGroupConversation)]
                                                                                           CreateGroupConversationResponse))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-group-conversation"
        (Summary "Create a new conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V6
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'MLSNonEmptyMemberList
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (Description
                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                     :> (ZLocalUser
                                                                         :> (ZOptConn
                                                                             :> ("conversations"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       NewConv
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              CreateGroupConversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 CreateGroupConversation)]
                                                                                          CreateGroupConversationResponse))))))))))))))))))))
      :<|> (Named
              "create-self-conversation@v2"
              (Summary "Create a self-conversation"
               :> (Until 'V3
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("self"
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V2 200 "Conversation existed" Conversation),
                                      WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V2 201 "Conversation created" Conversation)]
                                    (ResponseForExistedCreated Conversation))))))
            :<|> (Named
                    "create-self-conversation@v5"
                    (Summary "Create a self-conversation"
                     :> (From 'V3
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("self"
                                         :> MultiVerb
                                              'POST
                                              '[JSON]
                                              '[WithHeaders
                                                  ConversationHeaders
                                                  Conversation
                                                  (VersionedRespond
                                                     'V5 200 "Conversation existed" Conversation),
                                                WithHeaders
                                                  ConversationHeaders
                                                  Conversation
                                                  (VersionedRespond
                                                     'V5 201 "Conversation created" Conversation)]
                                              (ResponseForExistedCreated Conversation)))))))
                  :<|> (Named
                          "create-self-conversation"
                          (Summary "Create a self-conversation"
                           :> (From 'V6
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("self"
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V6 200 "Conversation existed" Conversation),
                                                  WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V6 201 "Conversation created" Conversation)]
                                                (ResponseForExistedCreated Conversation))))))
                        :<|> (Named
                                "get-mls-self-conversation@v5"
                                (Summary "Get the user's MLS self-conversation"
                                 :> (From 'V5
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("mls-self"
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[VersionedRespond
                                                                  'V5
                                                                  200
                                                                  "The MLS self-conversation"
                                                                  Conversation]
                                                              Conversation)))))))
                              :<|> (Named
                                      "get-mls-self-conversation"
                                      (Summary "Get the user's MLS self-conversation"
                                       :> (From 'V6
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("mls-self"
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "The MLS self-conversation"
                                                                    Conversation]
                                                                Conversation))))))
                                    :<|> (Named
                                            "get-subconversation"
                                            (Summary "Get information about an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "get-sub-conversation"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow
                                                                   'MLSSubConvUnsupportedConvType
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture
                                                                               "cnv" ConvId
                                                                             :> ("subconversations"
                                                                                 :> (Capture
                                                                                       "subconv"
                                                                                       SubConvId
                                                                                     :> MultiVerb
                                                                                          'GET
                                                                                          '[JSON]
                                                                                          '[Respond
                                                                                              200
                                                                                              "Subconversation"
                                                                                              PublicSubConversation]
                                                                                          PublicSubConversation)))))))))))
                                          :<|> (Named
                                                  "leave-subconversation"
                                                  (Summary "Leave an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Galley "leave-sub-conversation"
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow
                                                                             'MLSProtocolErrorTag
                                                                           :> (CanThrow
                                                                                 'MLSStaleMessage
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (ZLocalUser
                                                                                       :> (ZClient
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("subconversations"
                                                                                                       :> (Capture
                                                                                                             "subconv"
                                                                                                             SubConvId
                                                                                                           :> ("self"
                                                                                                               :> MultiVerb
                                                                                                                    'DELETE
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "OK"]
                                                                                                                    ()))))))))))))))))
                                                :<|> (Named
                                                        "delete-subconversation"
                                                        (Summary "Delete an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "delete-sub-conversation"
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'MLSStaleMessage
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("subconversations"
                                                                                                 :> (Capture
                                                                                                       "subconv"
                                                                                                       SubConvId
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           DeleteSubConversationRequest
                                                                                                         :> MultiVerb
                                                                                                              'DELETE
                                                                                                              '[JSON]
                                                                                                              '[Respond
                                                                                                                  200
                                                                                                                  "Deletion successful"
                                                                                                                  ()]
                                                                                                              ())))))))))))))
                                                      :<|> (Named
                                                              "get-subconversation-group-info"
                                                              (Summary
                                                                 "Get MLS group information of subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley "query-group-info"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'MLSMissingGroupInfo
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("subconversations"
                                                                                                   :> (Capture
                                                                                                         "subconv"
                                                                                                         SubConvId
                                                                                                       :> ("groupinfo"
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[MLS]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "The group information"
                                                                                                                    GroupInfoData]
                                                                                                                GroupInfoData))))))))))))
                                                            :<|> (Named
                                                                    "create-one-to-one-conversation@v2"
                                                                    (Summary
                                                                       "Create a 1:1 conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-created"
                                                                             :> (Until 'V3
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NoBindingTeamMembers
                                                                                             :> (CanThrow
                                                                                                   'NonBindingTeam
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           UnreachableBackendsLegacy
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("one2one"
                                                                                                                                         :> (VersionedReqBody
                                                                                                                                               'V2
                                                                                                                                               '[JSON]
                                                                                                                                               NewConv
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         200
                                                                                                                                                         "Conversation existed"
                                                                                                                                                         Conversation),
                                                                                                                                                    WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         201
                                                                                                                                                         "Conversation created"
                                                                                                                                                         Conversation)]
                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                     Conversation))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-one-to-one-conversation"
                                                                          (Summary
                                                                             "Create a 1:1 conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-created"
                                                                               :> (From 'V3
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'NoBindingTeamMembers
                                                                                               :> (CanThrow
                                                                                                     'NonBindingTeam
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'MissingLegalholdConsent
                                                                                                                       :> (CanThrow
                                                                                                                             UnreachableBackendsLegacy
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("one2one"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 NewConv
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V3
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V3
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           Conversation)]
                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                       Conversation)))))))))))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V5
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> (CanThrow
                                                                                                   'MLSNotEnabled
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                         :> ("conversations"
                                                                                                             :> ("one2one"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "usr"
                                                                                                                       UserId
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[VersionedRespond
                                                                                                                              'V5
                                                                                                                              200
                                                                                                                              "MLS 1-1 conversation"
                                                                                                                              Conversation]
                                                                                                                          Conversation))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V6
                                                                                           :> (Until
                                                                                                 'V7
                                                                                               :> (ZLocalUser
                                                                                                   :> (CanThrow
                                                                                                         'MLSNotEnabled
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> ("conversations"
                                                                                                               :> ("one2one"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "usr"
                                                                                                                         UserId
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                (MLSOne2OneConversation
                                                                                                                                   MLSPublicKey)]
                                                                                                                            (MLSOne2OneConversation
                                                                                                                               MLSPublicKey))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V7
                                                                                                 :> (ZLocalUser
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> ("conversations"
                                                                                                                 :> ("one2one"
                                                                                                                     :> (QualifiedCapture
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> (QueryParam
                                                                                                                               "format"
                                                                                                                               MLSPublicKeyFormat
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                         SomeKey)]
                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                     SomeKey))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                  (Summary
                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (Until
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     Invite
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                        (Summary
                                                                                                           "Add qualified members to an existing conversation."
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (Until
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation"
                                                                                                              (Summary
                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (From
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                     :> (Until
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TooManyMembers
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("join"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                           :> (Description
                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CodeNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidConversationPassword
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotATeamMember
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("join"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "code-check"
                                                                                                                                (Summary
                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                 :> (Description
                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'CodeNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> ("code-check"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationCode
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Valid"]
                                                                                                                                                                  ()))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                      (Summary
                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                       :> (Until
                                                                                                                                             'V4
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'WriteConversationsCode
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                               :> (ZUser
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                             :> (From
                                                                                                                                                   'V4
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                     :> (ZUser
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Delete conversation code"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'DELETE
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[Respond
                                                                                                                                                                                              200
                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                              Event]
                                                                                                                                                                                          Event))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-code"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'GET
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V2
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-group-conversation@v5"
        (Summary "Create a new conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V4
                             :> (Until 'V6
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSNonEmptyMemberList
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'MissingLegalholdConsent
                                                             :> (CanThrow NonFederatingBackends
                                                                 :> (CanThrow UnreachableBackends
                                                                     :> (Description
                                                                           "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                         :> (ZLocalUser
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewConv
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  CreateGroupConversation
                                                                                                  (VersionedRespond
                                                                                                     'V5
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     CreateGroupConversation)]
                                                                                              CreateGroupConversationResponse)))))))))))))))))))))
      :<|> (Named
              "create-group-conversation"
              (Summary "Create a new conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (From 'V6
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'MLSNonEmptyMemberList
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (Description
                                                                             "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                           :> (ZLocalUser
                                                                               :> (ZOptConn
                                                                                   :> ("conversations"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             NewConv
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    Conversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       200
                                                                                                       "Conversation existed"
                                                                                                       Conversation),
                                                                                                  WithHeaders
                                                                                                    ConversationHeaders
                                                                                                    CreateGroupConversation
                                                                                                    (VersionedRespond
                                                                                                       'V6
                                                                                                       201
                                                                                                       "Conversation created"
                                                                                                       CreateGroupConversation)]
                                                                                                CreateGroupConversationResponse))))))))))))))))))))
            :<|> (Named
                    "create-self-conversation@v2"
                    (Summary "Create a self-conversation"
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("self"
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V2 200 "Conversation existed" Conversation),
                                            WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V2 201 "Conversation created" Conversation)]
                                          (ResponseForExistedCreated Conversation))))))
                  :<|> (Named
                          "create-self-conversation@v5"
                          (Summary "Create a self-conversation"
                           :> (From 'V3
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("self"
                                               :> MultiVerb
                                                    'POST
                                                    '[JSON]
                                                    '[WithHeaders
                                                        ConversationHeaders
                                                        Conversation
                                                        (VersionedRespond
                                                           'V5
                                                           200
                                                           "Conversation existed"
                                                           Conversation),
                                                      WithHeaders
                                                        ConversationHeaders
                                                        Conversation
                                                        (VersionedRespond
                                                           'V5
                                                           201
                                                           "Conversation created"
                                                           Conversation)]
                                                    (ResponseForExistedCreated Conversation)))))))
                        :<|> (Named
                                "create-self-conversation"
                                (Summary "Create a self-conversation"
                                 :> (From 'V6
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("self"
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V6
                                                             200
                                                             "Conversation existed"
                                                             Conversation),
                                                        WithHeaders
                                                          ConversationHeaders
                                                          Conversation
                                                          (VersionedRespond
                                                             'V6
                                                             201
                                                             "Conversation created"
                                                             Conversation)]
                                                      (ResponseForExistedCreated Conversation))))))
                              :<|> (Named
                                      "get-mls-self-conversation@v5"
                                      (Summary "Get the user's MLS self-conversation"
                                       :> (From 'V5
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> ("mls-self"
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[VersionedRespond
                                                                        'V5
                                                                        200
                                                                        "The MLS self-conversation"
                                                                        Conversation]
                                                                    Conversation)))))))
                                    :<|> (Named
                                            "get-mls-self-conversation"
                                            (Summary "Get the user's MLS self-conversation"
                                             :> (From 'V6
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> ("mls-self"
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "The MLS self-conversation"
                                                                          Conversation]
                                                                      Conversation))))))
                                          :<|> (Named
                                                  "get-subconversation"
                                                  (Summary
                                                     "Get information about an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "get-sub-conversation"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow
                                                                         'MLSSubConvUnsupportedConvType
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture
                                                                                     "cnv" ConvId
                                                                                   :> ("subconversations"
                                                                                       :> (Capture
                                                                                             "subconv"
                                                                                             SubConvId
                                                                                           :> MultiVerb
                                                                                                'GET
                                                                                                '[JSON]
                                                                                                '[Respond
                                                                                                    200
                                                                                                    "Subconversation"
                                                                                                    PublicSubConversation]
                                                                                                PublicSubConversation)))))))))))
                                                :<|> (Named
                                                        "leave-subconversation"
                                                        (Summary "Leave an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "leave-sub-conversation"
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'MLSProtocolErrorTag
                                                                                 :> (CanThrow
                                                                                       'MLSStaleMessage
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (ZLocalUser
                                                                                             :> (ZClient
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("subconversations"
                                                                                                             :> (Capture
                                                                                                                   "subconv"
                                                                                                                   SubConvId
                                                                                                                 :> ("self"
                                                                                                                     :> MultiVerb
                                                                                                                          'DELETE
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "OK"]
                                                                                                                          ()))))))))))))))))
                                                      :<|> (Named
                                                              "delete-subconversation"
                                                              (Summary
                                                                 "Delete an MLS subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "delete-sub-conversation"
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (CanThrow
                                                                                         'MLSStaleMessage
                                                                                       :> (ZLocalUser
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("subconversations"
                                                                                                       :> (Capture
                                                                                                             "subconv"
                                                                                                             SubConvId
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 DeleteSubConversationRequest
                                                                                                               :> MultiVerb
                                                                                                                    'DELETE
                                                                                                                    '[JSON]
                                                                                                                    '[Respond
                                                                                                                        200
                                                                                                                        "Deletion successful"
                                                                                                                        ()]
                                                                                                                    ())))))))))))))
                                                            :<|> (Named
                                                                    "get-subconversation-group-info"
                                                                    (Summary
                                                                       "Get MLS group information of subconversation"
                                                                     :> (From 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "query-group-info"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'MLSMissingGroupInfo
                                                                                     :> (CanThrow
                                                                                           'MLSNotEnabled
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("subconversations"
                                                                                                         :> (Capture
                                                                                                               "subconv"
                                                                                                               SubConvId
                                                                                                             :> ("groupinfo"
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[MLS]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "The group information"
                                                                                                                          GroupInfoData]
                                                                                                                      GroupInfoData))))))))))))
                                                                  :<|> (Named
                                                                          "create-one-to-one-conversation@v2"
                                                                          (Summary
                                                                             "Create a 1:1 conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig "api-version"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-created"
                                                                                   :> (Until 'V3
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NoBindingTeamMembers
                                                                                                   :> (CanThrow
                                                                                                         'NonBindingTeam
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'NotConnected
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 UnreachableBackendsLegacy
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("one2one"
                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                     'V2
                                                                                                                                                     '[JSON]
                                                                                                                                                     NewConv
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               200
                                                                                                                                                               "Conversation existed"
                                                                                                                                                               Conversation),
                                                                                                                                                          WithHeaders
                                                                                                                                                            ConversationHeaders
                                                                                                                                                            Conversation
                                                                                                                                                            (VersionedRespond
                                                                                                                                                               'V2
                                                                                                                                                               201
                                                                                                                                                               "Conversation created"
                                                                                                                                                               Conversation)]
                                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                                           Conversation))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "create-one-to-one-conversation"
                                                                                (Summary
                                                                                   "Create a 1:1 conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-created"
                                                                                     :> (From 'V3
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'NoBindingTeamMembers
                                                                                                     :> (CanThrow
                                                                                                           'NonBindingTeam
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'MissingLegalholdConsent
                                                                                                                             :> (CanThrow
                                                                                                                                   UnreachableBackendsLegacy
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> ("one2one"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       NewConv
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V3
                                                                                                                                                                 200
                                                                                                                                                                 "Conversation existed"
                                                                                                                                                                 Conversation),
                                                                                                                                                            WithHeaders
                                                                                                                                                              ConversationHeaders
                                                                                                                                                              Conversation
                                                                                                                                                              (VersionedRespond
                                                                                                                                                                 'V3
                                                                                                                                                                 201
                                                                                                                                                                 "Conversation created"
                                                                                                                                                                 Conversation)]
                                                                                                                                                          (ResponseForExistedCreated
                                                                                                                                                             Conversation)))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation@v5"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V5
                                                                                           :> (Until
                                                                                                 'V6
                                                                                               :> (ZLocalUser
                                                                                                   :> (CanThrow
                                                                                                         'MLSNotEnabled
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MLSFederatedOne2OneNotSupported
                                                                                                               :> ("conversations"
                                                                                                                   :> ("one2one"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "usr"
                                                                                                                             UserId
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[VersionedRespond
                                                                                                                                    'V5
                                                                                                                                    200
                                                                                                                                    "MLS 1-1 conversation"
                                                                                                                                    Conversation]
                                                                                                                                Conversation))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation@v6"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V6
                                                                                                 :> (Until
                                                                                                       'V7
                                                                                                     :> (ZLocalUser
                                                                                                         :> (CanThrow
                                                                                                               'MLSNotEnabled
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("one2one"
                                                                                                                         :> (QualifiedCapture
                                                                                                                               "usr"
                                                                                                                               UserId
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                         MLSPublicKey)]
                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                     MLSPublicKey))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-one-to-one-mls-conversation"
                                                                                                  (Summary
                                                                                                     "Get an MLS 1:1 conversation"
                                                                                                   :> (From
                                                                                                         'V7
                                                                                                       :> (ZLocalUser
                                                                                                           :> (CanThrow
                                                                                                                 'MLSNotEnabled
                                                                                                               :> (CanThrow
                                                                                                                     'NotConnected
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("one2one"
                                                                                                                           :> (QualifiedCapture
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> (QueryParam
                                                                                                                                     "format"
                                                                                                                                     MLSPublicKeyFormat
                                                                                                                                   :> MultiVerb
                                                                                                                                        'GET
                                                                                                                                        '[JSON]
                                                                                                                                        '[Respond
                                                                                                                                            200
                                                                                                                                            "MLS 1-1 conversation"
                                                                                                                                            (MLSOne2OneConversation
                                                                                                                                               SomeKey)]
                                                                                                                                        (MLSOne2OneConversation
                                                                                                                                           SomeKey))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation-unqualified"
                                                                                                        (Summary
                                                                                                           "Add members to an existing conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (Until
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           Invite
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation-unqualified2"
                                                                                                              (Summary
                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (Until
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> ("v2"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "add-members-to-conversation"
                                                                                                                    (Summary
                                                                                                                       "Add qualified members to an existing conversation."
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (From
                                                                                                                                   'V2
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'AddConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'LeaveConversation)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'TooManyMembers
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotConnected
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'MissingLegalholdConsent
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           NonFederatingBackends
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               UnreachableBackends
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       InviteQualified
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'POST
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "join-conversation-by-id-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                           :> (Until
                                                                                                                                 'V5
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TooManyMembers
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("join"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "join-conversation-by-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Join a conversation using a reusable code"
                                                                                                                                 :> (Description
                                                                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CodeNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TooManyMembers
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> ("join"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               JoinConversationByCode
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvJoinResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "code-check"
                                                                                                                                      (Summary
                                                                                                                                         "Check validity of a conversation code."
                                                                                                                                       :> (Description
                                                                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'CodeNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidConversationPassword
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> ("code-check"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationCode
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Valid"]
                                                                                                                                                                        ()))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-conversation-code-unqualified@v3"
                                                                                                                                            (Summary
                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                             :> (Until
                                                                                                                                                   'V4
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                     :> (ZUser
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "create-conversation-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Create or recreate a conversation code"
                                                                                                                                                   :> (From
                                                                                                                                                         'V4
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'WriteConversationsCode
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'CreateConversationCodeConflict
                                                                                                                                                                           :> (ZUser
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZOptConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-conversation-guest-links-status"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-code-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Delete conversation code"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("code"
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'DELETE
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[Respond
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                                                                    Event]
                                                                                                                                                                                                Event))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-code"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get existing conversation code"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'CodeNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                                                     :> (ZHostOpt
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("code"
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'GET
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[Respond
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "member-typing-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'POST
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                                        ())))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "member-typing-qualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Sending typing notifications"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'POST
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-member-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                             'V2
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "remove-member"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "leave-conversation"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-other-member"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-group-conversation" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "brig" "get-not-fully-connected-backends",
   (HasAnnotation 'Remote "galley" "on-conversation-created",
    (HasAnnotation 'Remote "galley" "on-conversation-updated",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      CreateGroupConversationResponse)
-> Dict (HasAnnotation 'Remote "brig" "api-version")
-> Dict
     (HasAnnotation 'Remote "brig" "get-not-fully-connected-backends")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> Maybe ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSNonEmptyMemberList ()),
        Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      CreateGroupConversationResponse)
-> QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> Maybe ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSNonEmptyMemberList ()),
       Error (Tagged 'MLSNotEnabled ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     CreateGroupConversationResponse
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error FederationError) r, Member (Error InternalError) r,
 Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error NonFederatingBackends) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'MLSNonEmptyMemberList ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error UnreachableBackends) r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input Env) r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member LegalHoldStore r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Maybe ConnId -> NewConv -> Sem r CreateGroupConversationResponse
createGroupConversation))
    API
  (Named
     "create-group-conversation"
     (Summary "Create a new conversation"
      :> (MakesFederatedCall 'Brig "api-version"
          :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
              :> (MakesFederatedCall 'Galley "on-conversation-created"
                  :> (MakesFederatedCall 'Galley "on-conversation-updated"
                      :> (From 'V6
                          :> (CanThrow 'ConvAccessDenied
                              :> (CanThrow 'MLSNonEmptyMemberList
                                  :> (CanThrow 'MLSNotEnabled
                                      :> (CanThrow 'NotConnected
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow NonFederatingBackends
                                                          :> (CanThrow UnreachableBackends
                                                              :> (Description
                                                                    "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                  :> (ZLocalUser
                                                                      :> (ZOptConn
                                                                          :> ("conversations"
                                                                              :> (ReqBody
                                                                                    '[JSON] NewConv
                                                                                  :> MultiVerb
                                                                                       'POST
                                                                                       '[JSON]
                                                                                       '[WithHeaders
                                                                                           ConversationHeaders
                                                                                           Conversation
                                                                                           (VersionedRespond
                                                                                              'V6
                                                                                              200
                                                                                              "Conversation existed"
                                                                                              Conversation),
                                                                                         WithHeaders
                                                                                           ConversationHeaders
                                                                                           CreateGroupConversation
                                                                                           (VersionedRespond
                                                                                              'V6
                                                                                              201
                                                                                              "Conversation created"
                                                                                              CreateGroupConversation)]
                                                                                       CreateGroupConversationResponse)))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-self-conversation@v2"
        (Summary "Create a self-conversation"
         :> (Until 'V3
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("self"
                         :> MultiVerb
                              'POST
                              '[JSON]
                              '[WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V2 200 "Conversation existed" Conversation),
                                WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V2 201 "Conversation created" Conversation)]
                              (ResponseForExistedCreated Conversation))))))
      :<|> (Named
              "create-self-conversation@v5"
              (Summary "Create a self-conversation"
               :> (From 'V3
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("self"
                                   :> MultiVerb
                                        'POST
                                        '[JSON]
                                        '[WithHeaders
                                            ConversationHeaders
                                            Conversation
                                            (VersionedRespond
                                               'V5 200 "Conversation existed" Conversation),
                                          WithHeaders
                                            ConversationHeaders
                                            Conversation
                                            (VersionedRespond
                                               'V5 201 "Conversation created" Conversation)]
                                        (ResponseForExistedCreated Conversation)))))))
            :<|> (Named
                    "create-self-conversation"
                    (Summary "Create a self-conversation"
                     :> (From 'V6
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("self"
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V6 200 "Conversation existed" Conversation),
                                            WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V6 201 "Conversation created" Conversation)]
                                          (ResponseForExistedCreated Conversation))))))
                  :<|> (Named
                          "get-mls-self-conversation@v5"
                          (Summary "Get the user's MLS self-conversation"
                           :> (From 'V5
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("mls-self"
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[VersionedRespond
                                                            'V5
                                                            200
                                                            "The MLS self-conversation"
                                                            Conversation]
                                                        Conversation)))))))
                        :<|> (Named
                                "get-mls-self-conversation"
                                (Summary "Get the user's MLS self-conversation"
                                 :> (From 'V6
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("mls-self"
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "The MLS self-conversation"
                                                              Conversation]
                                                          Conversation))))))
                              :<|> (Named
                                      "get-subconversation"
                                      (Summary "Get information about an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSSubConvUnsupportedConvType
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("subconversations"
                                                                           :> (Capture
                                                                                 "subconv" SubConvId
                                                                               :> MultiVerb
                                                                                    'GET
                                                                                    '[JSON]
                                                                                    '[Respond
                                                                                        200
                                                                                        "Subconversation"
                                                                                        PublicSubConversation]
                                                                                    PublicSubConversation)))))))))))
                                    :<|> (Named
                                            "leave-subconversation"
                                            (Summary "Leave an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall
                                                           'Galley "leave-sub-conversation"
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'MLSProtocolErrorTag
                                                                     :> (CanThrow 'MLSStaleMessage
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (ZLocalUser
                                                                                 :> (ZClient
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("subconversations"
                                                                                                 :> (Capture
                                                                                                       "subconv"
                                                                                                       SubConvId
                                                                                                     :> ("self"
                                                                                                         :> MultiVerb
                                                                                                              'DELETE
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "OK"]
                                                                                                              ()))))))))))))))))
                                          :<|> (Named
                                                  "delete-subconversation"
                                                  (Summary "Delete an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "delete-sub-conversation"
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'MLSStaleMessage
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("subconversations"
                                                                                           :> (Capture
                                                                                                 "subconv"
                                                                                                 SubConvId
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     DeleteSubConversationRequest
                                                                                                   :> MultiVerb
                                                                                                        'DELETE
                                                                                                        '[JSON]
                                                                                                        '[Respond
                                                                                                            200
                                                                                                            "Deletion successful"
                                                                                                            ()]
                                                                                                        ())))))))))))))
                                                :<|> (Named
                                                        "get-subconversation-group-info"
                                                        (Summary
                                                           "Get MLS group information of subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "query-group-info"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'MLSMissingGroupInfo
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("subconversations"
                                                                                             :> (Capture
                                                                                                   "subconv"
                                                                                                   SubConvId
                                                                                                 :> ("groupinfo"
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[MLS]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "The group information"
                                                                                                              GroupInfoData]
                                                                                                          GroupInfoData))))))))))))
                                                      :<|> (Named
                                                              "create-one-to-one-conversation@v2"
                                                              (Summary "Create a 1:1 conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-created"
                                                                       :> (Until 'V3
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NoBindingTeamMembers
                                                                                       :> (CanThrow
                                                                                             'NonBindingTeam
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     UnreachableBackendsLegacy
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("one2one"
                                                                                                                                   :> (VersionedReqBody
                                                                                                                                         'V2
                                                                                                                                         '[JSON]
                                                                                                                                         NewConv
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   200
                                                                                                                                                   "Conversation existed"
                                                                                                                                                   Conversation),
                                                                                                                                              WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   201
                                                                                                                                                   "Conversation created"
                                                                                                                                                   Conversation)]
                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                               Conversation))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-one-to-one-conversation"
                                                                    (Summary
                                                                       "Create a 1:1 conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-created"
                                                                         :> (From 'V3
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'NoBindingTeamMembers
                                                                                         :> (CanThrow
                                                                                               'NonBindingTeam
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'MissingLegalholdConsent
                                                                                                                 :> (CanThrow
                                                                                                                       UnreachableBackendsLegacy
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("one2one"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           NewConv
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V3
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V3
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     Conversation)]
                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                 Conversation)))))))))))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation@v5"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V5
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> (CanThrow
                                                                                             'MLSNotEnabled
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                   :> ("conversations"
                                                                                                       :> ("one2one"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "usr"
                                                                                                                 UserId
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[VersionedRespond
                                                                                                                        'V5
                                                                                                                        200
                                                                                                                        "MLS 1-1 conversation"
                                                                                                                        Conversation]
                                                                                                                    Conversation))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V6
                                                                                     :> (Until 'V7
                                                                                         :> (ZLocalUser
                                                                                             :> (CanThrow
                                                                                                   'MLSNotEnabled
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> ("conversations"
                                                                                                         :> ("one2one"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "usr"
                                                                                                                   UserId
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "MLS 1-1 conversation"
                                                                                                                          (MLSOne2OneConversation
                                                                                                                             MLSPublicKey)]
                                                                                                                      (MLSOne2OneConversation
                                                                                                                         MLSPublicKey))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V7
                                                                                           :> (ZLocalUser
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> ("conversations"
                                                                                                           :> ("one2one"
                                                                                                               :> (QualifiedCapture
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> (QueryParam
                                                                                                                         "format"
                                                                                                                         MLSPublicKeyFormat
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                (MLSOne2OneConversation
                                                                                                                                   SomeKey)]
                                                                                                                            (MLSOne2OneConversation
                                                                                                                               SomeKey))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation-unqualified"
                                                                                            (Summary
                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (Until
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               Invite
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                  (Summary
                                                                                                     "Add qualified members to an existing conversation."
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (Until
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation"
                                                                                                        (Summary
                                                                                                           "Add qualified members to an existing conversation."
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (From
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                              (Summary
                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                               :> (Until
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TooManyMembers
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("join"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                     :> (Description
                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'CodeNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidConversationPassword
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotATeamMember
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TooManyMembers
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("join"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "code-check"
                                                                                                                          (Summary
                                                                                                                             "Check validity of a conversation code."
                                                                                                                           :> (Description
                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                               :> (CanThrow
                                                                                                                                     'CodeNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidConversationPassword
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> ("code-check"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationCode
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Valid"]
                                                                                                                                                            ()))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                (Summary
                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                 :> (Until
                                                                                                                                       'V4
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'WriteConversationsCode
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                         :> (ZUser
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                       :> (From
                                                                                                                                             'V4
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'WriteConversationsCode
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                               :> (ZUser
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                            (Summary
                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Delete conversation code"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("code"
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'DELETE
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[Respond
                                                                                                                                                                                        200
                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                        Event]
                                                                                                                                                                                    Event))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-code"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'CodeNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'GET
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'POST
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V2
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-member"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-group-conversation"
        (Summary "Create a new conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Brig "get-not-fully-connected-backends"
                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (From 'V6
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'MLSNonEmptyMemberList
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (Description
                                                                       "This returns 201 when a new conversation is created, and 200 when the conversation already existed"
                                                                     :> (ZLocalUser
                                                                         :> (ZOptConn
                                                                             :> ("conversations"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       NewConv
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[WithHeaders
                                                                                              ConversationHeaders
                                                                                              Conversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 200
                                                                                                 "Conversation existed"
                                                                                                 Conversation),
                                                                                            WithHeaders
                                                                                              ConversationHeaders
                                                                                              CreateGroupConversation
                                                                                              (VersionedRespond
                                                                                                 'V6
                                                                                                 201
                                                                                                 "Conversation created"
                                                                                                 CreateGroupConversation)]
                                                                                          CreateGroupConversationResponse))))))))))))))))))))
      :<|> (Named
              "create-self-conversation@v2"
              (Summary "Create a self-conversation"
               :> (Until 'V3
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("self"
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V2 200 "Conversation existed" Conversation),
                                      WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V2 201 "Conversation created" Conversation)]
                                    (ResponseForExistedCreated Conversation))))))
            :<|> (Named
                    "create-self-conversation@v5"
                    (Summary "Create a self-conversation"
                     :> (From 'V3
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("self"
                                         :> MultiVerb
                                              'POST
                                              '[JSON]
                                              '[WithHeaders
                                                  ConversationHeaders
                                                  Conversation
                                                  (VersionedRespond
                                                     'V5 200 "Conversation existed" Conversation),
                                                WithHeaders
                                                  ConversationHeaders
                                                  Conversation
                                                  (VersionedRespond
                                                     'V5 201 "Conversation created" Conversation)]
                                              (ResponseForExistedCreated Conversation)))))))
                  :<|> (Named
                          "create-self-conversation"
                          (Summary "Create a self-conversation"
                           :> (From 'V6
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("self"
                                           :> MultiVerb
                                                'POST
                                                '[JSON]
                                                '[WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V6 200 "Conversation existed" Conversation),
                                                  WithHeaders
                                                    ConversationHeaders
                                                    Conversation
                                                    (VersionedRespond
                                                       'V6 201 "Conversation created" Conversation)]
                                                (ResponseForExistedCreated Conversation))))))
                        :<|> (Named
                                "get-mls-self-conversation@v5"
                                (Summary "Get the user's MLS self-conversation"
                                 :> (From 'V5
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> ("mls-self"
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[VersionedRespond
                                                                  'V5
                                                                  200
                                                                  "The MLS self-conversation"
                                                                  Conversation]
                                                              Conversation)))))))
                              :<|> (Named
                                      "get-mls-self-conversation"
                                      (Summary "Get the user's MLS self-conversation"
                                       :> (From 'V6
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> ("mls-self"
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "The MLS self-conversation"
                                                                    Conversation]
                                                                Conversation))))))
                                    :<|> (Named
                                            "get-subconversation"
                                            (Summary "Get information about an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "get-sub-conversation"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow
                                                                   'MLSSubConvUnsupportedConvType
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture
                                                                               "cnv" ConvId
                                                                             :> ("subconversations"
                                                                                 :> (Capture
                                                                                       "subconv"
                                                                                       SubConvId
                                                                                     :> MultiVerb
                                                                                          'GET
                                                                                          '[JSON]
                                                                                          '[Respond
                                                                                              200
                                                                                              "Subconversation"
                                                                                              PublicSubConversation]
                                                                                          PublicSubConversation)))))))))))
                                          :<|> (Named
                                                  "leave-subconversation"
                                                  (Summary "Leave an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Galley "leave-sub-conversation"
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow
                                                                             'MLSProtocolErrorTag
                                                                           :> (CanThrow
                                                                                 'MLSStaleMessage
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (ZLocalUser
                                                                                       :> (ZClient
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("subconversations"
                                                                                                       :> (Capture
                                                                                                             "subconv"
                                                                                                             SubConvId
                                                                                                           :> ("self"
                                                                                                               :> MultiVerb
                                                                                                                    'DELETE
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "OK"]
                                                                                                                    ()))))))))))))))))
                                                :<|> (Named
                                                        "delete-subconversation"
                                                        (Summary "Delete an MLS subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "delete-sub-conversation"
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (CanThrow
                                                                                   'MLSStaleMessage
                                                                                 :> (ZLocalUser
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("subconversations"
                                                                                                 :> (Capture
                                                                                                       "subconv"
                                                                                                       SubConvId
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           DeleteSubConversationRequest
                                                                                                         :> MultiVerb
                                                                                                              'DELETE
                                                                                                              '[JSON]
                                                                                                              '[Respond
                                                                                                                  200
                                                                                                                  "Deletion successful"
                                                                                                                  ()]
                                                                                                              ())))))))))))))
                                                      :<|> (Named
                                                              "get-subconversation-group-info"
                                                              (Summary
                                                                 "Get MLS group information of subconversation"
                                                               :> (From 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley "query-group-info"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'MLSMissingGroupInfo
                                                                               :> (CanThrow
                                                                                     'MLSNotEnabled
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("subconversations"
                                                                                                   :> (Capture
                                                                                                         "subconv"
                                                                                                         SubConvId
                                                                                                       :> ("groupinfo"
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[MLS]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "The group information"
                                                                                                                    GroupInfoData]
                                                                                                                GroupInfoData))))))))))))
                                                            :<|> (Named
                                                                    "create-one-to-one-conversation@v2"
                                                                    (Summary
                                                                       "Create a 1:1 conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "api-version"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-created"
                                                                             :> (Until 'V3
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NoBindingTeamMembers
                                                                                             :> (CanThrow
                                                                                                   'NonBindingTeam
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'NotConnected
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           UnreachableBackendsLegacy
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("one2one"
                                                                                                                                         :> (VersionedReqBody
                                                                                                                                               'V2
                                                                                                                                               '[JSON]
                                                                                                                                               NewConv
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         200
                                                                                                                                                         "Conversation existed"
                                                                                                                                                         Conversation),
                                                                                                                                                    WithHeaders
                                                                                                                                                      ConversationHeaders
                                                                                                                                                      Conversation
                                                                                                                                                      (VersionedRespond
                                                                                                                                                         'V2
                                                                                                                                                         201
                                                                                                                                                         "Conversation created"
                                                                                                                                                         Conversation)]
                                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                                     Conversation))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "create-one-to-one-conversation"
                                                                          (Summary
                                                                             "Create a 1:1 conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-created"
                                                                               :> (From 'V3
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'NoBindingTeamMembers
                                                                                               :> (CanThrow
                                                                                                     'NonBindingTeam
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'MissingLegalholdConsent
                                                                                                                       :> (CanThrow
                                                                                                                             UnreachableBackendsLegacy
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> ("one2one"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 NewConv
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V3
                                                                                                                                                           200
                                                                                                                                                           "Conversation existed"
                                                                                                                                                           Conversation),
                                                                                                                                                      WithHeaders
                                                                                                                                                        ConversationHeaders
                                                                                                                                                        Conversation
                                                                                                                                                        (VersionedRespond
                                                                                                                                                           'V3
                                                                                                                                                           201
                                                                                                                                                           "Conversation created"
                                                                                                                                                           Conversation)]
                                                                                                                                                    (ResponseForExistedCreated
                                                                                                                                                       Conversation)))))))))))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation@v5"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V5
                                                                                     :> (Until 'V6
                                                                                         :> (ZLocalUser
                                                                                             :> (CanThrow
                                                                                                   'MLSNotEnabled
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MLSFederatedOne2OneNotSupported
                                                                                                         :> ("conversations"
                                                                                                             :> ("one2one"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "usr"
                                                                                                                       UserId
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[VersionedRespond
                                                                                                                              'V5
                                                                                                                              200
                                                                                                                              "MLS 1-1 conversation"
                                                                                                                              Conversation]
                                                                                                                          Conversation))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation@v6"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V6
                                                                                           :> (Until
                                                                                                 'V7
                                                                                               :> (ZLocalUser
                                                                                                   :> (CanThrow
                                                                                                         'MLSNotEnabled
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> ("conversations"
                                                                                                               :> ("one2one"
                                                                                                                   :> (QualifiedCapture
                                                                                                                         "usr"
                                                                                                                         UserId
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                (MLSOne2OneConversation
                                                                                                                                   MLSPublicKey)]
                                                                                                                            (MLSOne2OneConversation
                                                                                                                               MLSPublicKey))))))))))
                                                                                    :<|> (Named
                                                                                            "get-one-to-one-mls-conversation"
                                                                                            (Summary
                                                                                               "Get an MLS 1:1 conversation"
                                                                                             :> (From
                                                                                                   'V7
                                                                                                 :> (ZLocalUser
                                                                                                     :> (CanThrow
                                                                                                           'MLSNotEnabled
                                                                                                         :> (CanThrow
                                                                                                               'NotConnected
                                                                                                             :> ("conversations"
                                                                                                                 :> ("one2one"
                                                                                                                     :> (QualifiedCapture
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> (QueryParam
                                                                                                                               "format"
                                                                                                                               MLSPublicKeyFormat
                                                                                                                             :> MultiVerb
                                                                                                                                  'GET
                                                                                                                                  '[JSON]
                                                                                                                                  '[Respond
                                                                                                                                      200
                                                                                                                                      "MLS 1-1 conversation"
                                                                                                                                      (MLSOne2OneConversation
                                                                                                                                         SomeKey)]
                                                                                                                                  (MLSOne2OneConversation
                                                                                                                                     SomeKey))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation-unqualified"
                                                                                                  (Summary
                                                                                                     "Add members to an existing conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (Until
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     Invite
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation-unqualified2"
                                                                                                        (Summary
                                                                                                           "Add qualified members to an existing conversation."
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (Until
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> ("v2"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               InviteQualified
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "add-members-to-conversation"
                                                                                                              (Summary
                                                                                                                 "Add qualified members to an existing conversation."
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (From
                                                                                                                             'V2
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'AddConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'LeaveConversation)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'TooManyMembers
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotConnected
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'MissingLegalholdConsent
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     NonFederatingBackends
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         UnreachableBackends
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 InviteQualified
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'POST
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "join-conversation-by-id-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                                     :> (Until
                                                                                                                           'V5
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TooManyMembers
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("join"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "join-conversation-by-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Join a conversation using a reusable code"
                                                                                                                           :> (Description
                                                                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CodeNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidConversationPassword
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'NotATeamMember
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TooManyMembers
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> ("join"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         JoinConversationByCode
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvJoinResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "code-check"
                                                                                                                                (Summary
                                                                                                                                   "Check validity of a conversation code."
                                                                                                                                 :> (Description
                                                                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'CodeNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidConversationPassword
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> ("code-check"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationCode
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Valid"]
                                                                                                                                                                  ()))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-conversation-code-unqualified@v3"
                                                                                                                                      (Summary
                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                       :> (Until
                                                                                                                                             'V4
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'WriteConversationsCode
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                               :> (ZUser
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "create-conversation-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Create or recreate a conversation code"
                                                                                                                                             :> (From
                                                                                                                                                   'V4
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'WriteConversationsCode
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'CreateConversationCodeConflict
                                                                                                                                                                     :> (ZUser
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZOptConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-conversation-guest-links-status"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-code-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Delete conversation code"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("code"
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'DELETE
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[Respond
                                                                                                                                                                                              200
                                                                                                                                                                                              "Conversation code deleted."
                                                                                                                                                                                              Event]
                                                                                                                                                                                          Event))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-code"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get existing conversation code"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'CodeNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                                                               :> (ZHostOpt
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("code"
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'GET
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[Respond
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Conversation Code"
                                                                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "member-typing-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'POST
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                                  ())))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "member-typing-qualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Sending typing notifications"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "update-typing-indicator"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("typing"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 TypingStatus
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'POST
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-member-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                       'V2
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "remove-member"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "leave-conversation"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-other-member"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-self-conversation@v2" ServerT
  (Summary "Create a self-conversation"
   :> (Until 'V3
       :> (ZLocalUser
           :> ("conversations"
               :> ("self"
                   :> MultiVerb
                        'POST
                        '[JSON]
                        '[WithHeaders
                            ConversationHeaders
                            Conversation
                            (VersionedRespond 'V2 200 "Conversation existed" Conversation),
                          WithHeaders
                            ConversationHeaders
                            Conversation
                            (VersionedRespond 'V2 201 "Conversation created" Conversation)]
                        (ResponseForExistedCreated Conversation))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Create a self-conversation"
            :> (Until 'V3
                :> (ZLocalUser
                    :> ("conversations"
                        :> ("self"
                            :> MultiVerb
                                 'POST
                                 '[JSON]
                                 '[WithHeaders
                                     ConversationHeaders
                                     Conversation
                                     (VersionedRespond 'V2 200 "Conversation existed" Conversation),
                                   WithHeaders
                                     ConversationHeaders
                                     Conversation
                                     (VersionedRespond 'V2 201 "Conversation created" Conversation)]
                                 (ResponseForExistedCreated Conversation)))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Sem r (ConversationResponse Conversation)
createProteusSelfConversation
    API
  (Named
     "create-self-conversation@v2"
     (Summary "Create a self-conversation"
      :> (Until 'V3
          :> (ZLocalUser
              :> ("conversations"
                  :> ("self"
                      :> MultiVerb
                           'POST
                           '[JSON]
                           '[WithHeaders
                               ConversationHeaders
                               Conversation
                               (VersionedRespond 'V2 200 "Conversation existed" Conversation),
                             WithHeaders
                               ConversationHeaders
                               Conversation
                               (VersionedRespond 'V2 201 "Conversation created" Conversation)]
                           (ResponseForExistedCreated Conversation)))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-self-conversation@v5"
        (Summary "Create a self-conversation"
         :> (From 'V3
             :> (Until 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("self"
                             :> MultiVerb
                                  'POST
                                  '[JSON]
                                  '[WithHeaders
                                      ConversationHeaders
                                      Conversation
                                      (VersionedRespond
                                         'V5 200 "Conversation existed" Conversation),
                                    WithHeaders
                                      ConversationHeaders
                                      Conversation
                                      (VersionedRespond
                                         'V5 201 "Conversation created" Conversation)]
                                  (ResponseForExistedCreated Conversation)))))))
      :<|> (Named
              "create-self-conversation"
              (Summary "Create a self-conversation"
               :> (From 'V6
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("self"
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V6 200 "Conversation existed" Conversation),
                                      WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V6 201 "Conversation created" Conversation)]
                                    (ResponseForExistedCreated Conversation))))))
            :<|> (Named
                    "get-mls-self-conversation@v5"
                    (Summary "Get the user's MLS self-conversation"
                     :> (From 'V5
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("mls-self"
                                         :> (CanThrow 'MLSNotEnabled
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[VersionedRespond
                                                      'V5
                                                      200
                                                      "The MLS self-conversation"
                                                      Conversation]
                                                  Conversation)))))))
                  :<|> (Named
                          "get-mls-self-conversation"
                          (Summary "Get the user's MLS self-conversation"
                           :> (From 'V6
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("mls-self"
                                           :> (CanThrow 'MLSNotEnabled
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "The MLS self-conversation"
                                                        Conversation]
                                                    Conversation))))))
                        :<|> (Named
                                "get-subconversation"
                                (Summary "Get information about an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSSubConvUnsupportedConvType
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("subconversations"
                                                                     :> (Capture "subconv" SubConvId
                                                                         :> MultiVerb
                                                                              'GET
                                                                              '[JSON]
                                                                              '[Respond
                                                                                  200
                                                                                  "Subconversation"
                                                                                  PublicSubConversation]
                                                                              PublicSubConversation)))))))))))
                              :<|> (Named
                                      "leave-subconversation"
                                      (Summary "Leave an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall
                                                     'Galley "leave-sub-conversation"
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'MLSProtocolErrorTag
                                                               :> (CanThrow 'MLSStaleMessage
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (ZLocalUser
                                                                           :> (ZClient
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("subconversations"
                                                                                           :> (Capture
                                                                                                 "subconv"
                                                                                                 SubConvId
                                                                                               :> ("self"
                                                                                                   :> MultiVerb
                                                                                                        'DELETE
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "OK"]
                                                                                                        ()))))))))))))))))
                                    :<|> (Named
                                            "delete-subconversation"
                                            (Summary "Delete an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "delete-sub-conversation"
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'MLSStaleMessage
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("subconversations"
                                                                                     :> (Capture
                                                                                           "subconv"
                                                                                           SubConvId
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               DeleteSubConversationRequest
                                                                                             :> MultiVerb
                                                                                                  'DELETE
                                                                                                  '[JSON]
                                                                                                  '[Respond
                                                                                                      200
                                                                                                      "Deletion successful"
                                                                                                      ()]
                                                                                                  ())))))))))))))
                                          :<|> (Named
                                                  "get-subconversation-group-info"
                                                  (Summary
                                                     "Get MLS group information of subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "query-group-info"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'MLSMissingGroupInfo
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture
                                                                                     "cnv" ConvId
                                                                                   :> ("subconversations"
                                                                                       :> (Capture
                                                                                             "subconv"
                                                                                             SubConvId
                                                                                           :> ("groupinfo"
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[MLS]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "The group information"
                                                                                                        GroupInfoData]
                                                                                                    GroupInfoData))))))))))))
                                                :<|> (Named
                                                        "create-one-to-one-conversation@v2"
                                                        (Summary "Create a 1:1 conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-created"
                                                                 :> (Until 'V3
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NoBindingTeamMembers
                                                                                 :> (CanThrow
                                                                                       'NonBindingTeam
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               UnreachableBackendsLegacy
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("one2one"
                                                                                                                             :> (VersionedReqBody
                                                                                                                                   'V2
                                                                                                                                   '[JSON]
                                                                                                                                   NewConv
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             200
                                                                                                                                             "Conversation existed"
                                                                                                                                             Conversation),
                                                                                                                                        WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             201
                                                                                                                                             "Conversation created"
                                                                                                                                             Conversation)]
                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                         Conversation))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-one-to-one-conversation"
                                                              (Summary "Create a 1:1 conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-created"
                                                                   :> (From 'V3
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'NoBindingTeamMembers
                                                                                   :> (CanThrow
                                                                                         'NonBindingTeam
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             'MissingLegalholdConsent
                                                                                                           :> (CanThrow
                                                                                                                 UnreachableBackendsLegacy
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("one2one"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     NewConv
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V3
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V3
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               Conversation)]
                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                           Conversation)))))))))))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation@v5"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V5
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> (CanThrow
                                                                                       'MLSNotEnabled
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                             :> ("conversations"
                                                                                                 :> ("one2one"
                                                                                                     :> (QualifiedCapture
                                                                                                           "usr"
                                                                                                           UserId
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[VersionedRespond
                                                                                                                  'V5
                                                                                                                  200
                                                                                                                  "MLS 1-1 conversation"
                                                                                                                  Conversation]
                                                                                                              Conversation))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation@v6"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V6
                                                                               :> (Until 'V7
                                                                                   :> (ZLocalUser
                                                                                       :> (CanThrow
                                                                                             'MLSNotEnabled
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> ("conversations"
                                                                                                   :> ("one2one"
                                                                                                       :> (QualifiedCapture
                                                                                                             "usr"
                                                                                                             UserId
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "MLS 1-1 conversation"
                                                                                                                    (MLSOne2OneConversation
                                                                                                                       MLSPublicKey)]
                                                                                                                (MLSOne2OneConversation
                                                                                                                   MLSPublicKey))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V7
                                                                                     :> (ZLocalUser
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> ("conversations"
                                                                                                     :> ("one2one"
                                                                                                         :> (QualifiedCapture
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> (QueryParam
                                                                                                                   "format"
                                                                                                                   MLSPublicKeyFormat
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "MLS 1-1 conversation"
                                                                                                                          (MLSOne2OneConversation
                                                                                                                             SomeKey)]
                                                                                                                      (MLSOne2OneConversation
                                                                                                                         SomeKey))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation-unqualified"
                                                                                      (Summary
                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (Until
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         Invite
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation-unqualified2"
                                                                                            (Summary
                                                                                               "Add qualified members to an existing conversation."
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (Until
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> ("v2"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation"
                                                                                                  (Summary
                                                                                                     "Add qualified members to an existing conversation."
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (From
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                        (Summary
                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                         :> (Until
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TooManyMembers
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("join"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvJoinResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Join a conversation using a reusable code"
                                                                                                               :> (Description
                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'CodeNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidConversationPassword
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'GuestLinksDisabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TooManyMembers
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("join"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "code-check"
                                                                                                                    (Summary
                                                                                                                       "Check validity of a conversation code."
                                                                                                                     :> (Description
                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                         :> (CanThrow
                                                                                                                               'CodeNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidConversationPassword
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> ("code-check"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationCode
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Valid"]
                                                                                                                                                      ()))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                          (Summary
                                                                                                                             "Create or recreate a conversation code"
                                                                                                                           :> (Until
                                                                                                                                 'V4
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'WriteConversationsCode
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                   :> (ZUser
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                 :> (From
                                                                                                                                       'V4
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'WriteConversationsCode
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                         :> (ZUser
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                      (Summary
                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Delete conversation code"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("code"
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'DELETE
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[Respond
                                                                                                                                                                                  200
                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                  Event]
                                                                                                                                                                              Event))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-code"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'CodeNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'GET
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                200
                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V2
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-member"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-self-conversation@v2"
        (Summary "Create a self-conversation"
         :> (Until 'V3
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("self"
                         :> MultiVerb
                              'POST
                              '[JSON]
                              '[WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V2 200 "Conversation existed" Conversation),
                                WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V2 201 "Conversation created" Conversation)]
                              (ResponseForExistedCreated Conversation))))))
      :<|> (Named
              "create-self-conversation@v5"
              (Summary "Create a self-conversation"
               :> (From 'V3
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("self"
                                   :> MultiVerb
                                        'POST
                                        '[JSON]
                                        '[WithHeaders
                                            ConversationHeaders
                                            Conversation
                                            (VersionedRespond
                                               'V5 200 "Conversation existed" Conversation),
                                          WithHeaders
                                            ConversationHeaders
                                            Conversation
                                            (VersionedRespond
                                               'V5 201 "Conversation created" Conversation)]
                                        (ResponseForExistedCreated Conversation)))))))
            :<|> (Named
                    "create-self-conversation"
                    (Summary "Create a self-conversation"
                     :> (From 'V6
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("self"
                                     :> MultiVerb
                                          'POST
                                          '[JSON]
                                          '[WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V6 200 "Conversation existed" Conversation),
                                            WithHeaders
                                              ConversationHeaders
                                              Conversation
                                              (VersionedRespond
                                                 'V6 201 "Conversation created" Conversation)]
                                          (ResponseForExistedCreated Conversation))))))
                  :<|> (Named
                          "get-mls-self-conversation@v5"
                          (Summary "Get the user's MLS self-conversation"
                           :> (From 'V5
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> ("mls-self"
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[VersionedRespond
                                                            'V5
                                                            200
                                                            "The MLS self-conversation"
                                                            Conversation]
                                                        Conversation)))))))
                        :<|> (Named
                                "get-mls-self-conversation"
                                (Summary "Get the user's MLS self-conversation"
                                 :> (From 'V6
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> ("mls-self"
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "The MLS self-conversation"
                                                              Conversation]
                                                          Conversation))))))
                              :<|> (Named
                                      "get-subconversation"
                                      (Summary "Get information about an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'MLSSubConvUnsupportedConvType
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("subconversations"
                                                                           :> (Capture
                                                                                 "subconv" SubConvId
                                                                               :> MultiVerb
                                                                                    'GET
                                                                                    '[JSON]
                                                                                    '[Respond
                                                                                        200
                                                                                        "Subconversation"
                                                                                        PublicSubConversation]
                                                                                    PublicSubConversation)))))))))))
                                    :<|> (Named
                                            "leave-subconversation"
                                            (Summary "Leave an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall
                                                           'Galley "leave-sub-conversation"
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'MLSProtocolErrorTag
                                                                     :> (CanThrow 'MLSStaleMessage
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (ZLocalUser
                                                                                 :> (ZClient
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("subconversations"
                                                                                                 :> (Capture
                                                                                                       "subconv"
                                                                                                       SubConvId
                                                                                                     :> ("self"
                                                                                                         :> MultiVerb
                                                                                                              'DELETE
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "OK"]
                                                                                                              ()))))))))))))))))
                                          :<|> (Named
                                                  "delete-subconversation"
                                                  (Summary "Delete an MLS subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "delete-sub-conversation"
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (CanThrow 'MLSStaleMessage
                                                                           :> (ZLocalUser
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("subconversations"
                                                                                           :> (Capture
                                                                                                 "subconv"
                                                                                                 SubConvId
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     DeleteSubConversationRequest
                                                                                                   :> MultiVerb
                                                                                                        'DELETE
                                                                                                        '[JSON]
                                                                                                        '[Respond
                                                                                                            200
                                                                                                            "Deletion successful"
                                                                                                            ()]
                                                                                                        ())))))))))))))
                                                :<|> (Named
                                                        "get-subconversation-group-info"
                                                        (Summary
                                                           "Get MLS group information of subconversation"
                                                         :> (From 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "query-group-info"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'MLSMissingGroupInfo
                                                                         :> (CanThrow 'MLSNotEnabled
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("subconversations"
                                                                                             :> (Capture
                                                                                                   "subconv"
                                                                                                   SubConvId
                                                                                                 :> ("groupinfo"
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[MLS]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "The group information"
                                                                                                              GroupInfoData]
                                                                                                          GroupInfoData))))))))))))
                                                      :<|> (Named
                                                              "create-one-to-one-conversation@v2"
                                                              (Summary "Create a 1:1 conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "api-version"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-created"
                                                                       :> (Until 'V3
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NoBindingTeamMembers
                                                                                       :> (CanThrow
                                                                                             'NonBindingTeam
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'NotConnected
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     UnreachableBackendsLegacy
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("one2one"
                                                                                                                                   :> (VersionedReqBody
                                                                                                                                         'V2
                                                                                                                                         '[JSON]
                                                                                                                                         NewConv
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   200
                                                                                                                                                   "Conversation existed"
                                                                                                                                                   Conversation),
                                                                                                                                              WithHeaders
                                                                                                                                                ConversationHeaders
                                                                                                                                                Conversation
                                                                                                                                                (VersionedRespond
                                                                                                                                                   'V2
                                                                                                                                                   201
                                                                                                                                                   "Conversation created"
                                                                                                                                                   Conversation)]
                                                                                                                                            (ResponseForExistedCreated
                                                                                                                                               Conversation))))))))))))))))))))
                                                            :<|> (Named
                                                                    "create-one-to-one-conversation"
                                                                    (Summary
                                                                       "Create a 1:1 conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-created"
                                                                         :> (From 'V3
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'NoBindingTeamMembers
                                                                                         :> (CanThrow
                                                                                               'NonBindingTeam
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'MissingLegalholdConsent
                                                                                                                 :> (CanThrow
                                                                                                                       UnreachableBackendsLegacy
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> ("one2one"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           NewConv
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              '[WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V3
                                                                                                                                                     200
                                                                                                                                                     "Conversation existed"
                                                                                                                                                     Conversation),
                                                                                                                                                WithHeaders
                                                                                                                                                  ConversationHeaders
                                                                                                                                                  Conversation
                                                                                                                                                  (VersionedRespond
                                                                                                                                                     'V3
                                                                                                                                                     201
                                                                                                                                                     "Conversation created"
                                                                                                                                                     Conversation)]
                                                                                                                                              (ResponseForExistedCreated
                                                                                                                                                 Conversation)))))))))))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation@v5"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V5
                                                                               :> (Until 'V6
                                                                                   :> (ZLocalUser
                                                                                       :> (CanThrow
                                                                                             'MLSNotEnabled
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MLSFederatedOne2OneNotSupported
                                                                                                   :> ("conversations"
                                                                                                       :> ("one2one"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "usr"
                                                                                                                 UserId
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[VersionedRespond
                                                                                                                        'V5
                                                                                                                        200
                                                                                                                        "MLS 1-1 conversation"
                                                                                                                        Conversation]
                                                                                                                    Conversation))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation@v6"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V6
                                                                                     :> (Until 'V7
                                                                                         :> (ZLocalUser
                                                                                             :> (CanThrow
                                                                                                   'MLSNotEnabled
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> ("conversations"
                                                                                                         :> ("one2one"
                                                                                                             :> (QualifiedCapture
                                                                                                                   "usr"
                                                                                                                   UserId
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "MLS 1-1 conversation"
                                                                                                                          (MLSOne2OneConversation
                                                                                                                             MLSPublicKey)]
                                                                                                                      (MLSOne2OneConversation
                                                                                                                         MLSPublicKey))))))))))
                                                                              :<|> (Named
                                                                                      "get-one-to-one-mls-conversation"
                                                                                      (Summary
                                                                                         "Get an MLS 1:1 conversation"
                                                                                       :> (From 'V7
                                                                                           :> (ZLocalUser
                                                                                               :> (CanThrow
                                                                                                     'MLSNotEnabled
                                                                                                   :> (CanThrow
                                                                                                         'NotConnected
                                                                                                       :> ("conversations"
                                                                                                           :> ("one2one"
                                                                                                               :> (QualifiedCapture
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> (QueryParam
                                                                                                                         "format"
                                                                                                                         MLSPublicKeyFormat
                                                                                                                       :> MultiVerb
                                                                                                                            'GET
                                                                                                                            '[JSON]
                                                                                                                            '[Respond
                                                                                                                                200
                                                                                                                                "MLS 1-1 conversation"
                                                                                                                                (MLSOne2OneConversation
                                                                                                                                   SomeKey)]
                                                                                                                            (MLSOne2OneConversation
                                                                                                                               SomeKey))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation-unqualified"
                                                                                            (Summary
                                                                                               "Add members to an existing conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (Until
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               Invite
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation-unqualified2"
                                                                                                  (Summary
                                                                                                     "Add qualified members to an existing conversation."
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (Until
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> ("v2"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         InviteQualified
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "add-members-to-conversation"
                                                                                                        (Summary
                                                                                                           "Add qualified members to an existing conversation."
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (From
                                                                                                                       'V2
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'AddConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'LeaveConversation)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TooManyMembers
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotConnected
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'MissingLegalholdConsent
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               NonFederatingBackends
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   UnreachableBackends
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           InviteQualified
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'POST
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "join-conversation-by-id-unqualified"
                                                                                                              (Summary
                                                                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                               :> (Until
                                                                                                                     'V5
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TooManyMembers
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("join"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "join-conversation-by-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Join a conversation using a reusable code"
                                                                                                                     :> (Description
                                                                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'CodeNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidConversationPassword
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'NotATeamMember
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TooManyMembers
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> ("join"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   JoinConversationByCode
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvJoinResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "code-check"
                                                                                                                          (Summary
                                                                                                                             "Check validity of a conversation code."
                                                                                                                           :> (Description
                                                                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                               :> (CanThrow
                                                                                                                                     'CodeNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidConversationPassword
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> ("code-check"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationCode
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Valid"]
                                                                                                                                                            ()))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-conversation-code-unqualified@v3"
                                                                                                                                (Summary
                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                 :> (Until
                                                                                                                                       'V4
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'WriteConversationsCode
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                         :> (ZUser
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "create-conversation-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Create or recreate a conversation code"
                                                                                                                                       :> (From
                                                                                                                                             'V4
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'WriteConversationsCode
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'GuestLinksDisabled
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'CreateConversationCodeConflict
                                                                                                                                                               :> (ZUser
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZOptConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-conversation-guest-links-status"
                                                                                                                                            (Summary
                                                                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 GuestLinksConfig)))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-code-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Delete conversation code"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("code"
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'DELETE
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[Respond
                                                                                                                                                                                        200
                                                                                                                                                                                        "Conversation code deleted."
                                                                                                                                                                                        Event]
                                                                                                                                                                                    Event))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-code"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get existing conversation code"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'CodeNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'GuestLinksDisabled
                                                                                                                                                                         :> (ZHostOpt
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("code"
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'GET
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[Respond
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Conversation Code"
                                                                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "member-typing-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'POST
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                                            ())))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "member-typing-qualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Sending typing notifications"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "update-typing-indicator"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("typing"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           TypingStatus
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'POST
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-member-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V2
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "remove-member"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "leave-conversation"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-other-member"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update membership of the specified user"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-name"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update conversation name"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-self-conversation@v5" ServerT
  (Summary "Create a self-conversation"
   :> (From 'V3
       :> (Until 'V6
           :> (ZLocalUser
               :> ("conversations"
                   :> ("self"
                       :> MultiVerb
                            'POST
                            '[JSON]
                            '[WithHeaders
                                ConversationHeaders
                                Conversation
                                (VersionedRespond 'V5 200 "Conversation existed" Conversation),
                              WithHeaders
                                ConversationHeaders
                                Conversation
                                (VersionedRespond 'V5 201 "Conversation created" Conversation)]
                            (ResponseForExistedCreated Conversation)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Create a self-conversation"
            :> (From 'V3
                :> (Until 'V6
                    :> (ZLocalUser
                        :> ("conversations"
                            :> ("self"
                                :> MultiVerb
                                     'POST
                                     '[JSON]
                                     '[WithHeaders
                                         ConversationHeaders
                                         Conversation
                                         (VersionedRespond
                                            'V5 200 "Conversation existed" Conversation),
                                       WithHeaders
                                         ConversationHeaders
                                         Conversation
                                         (VersionedRespond
                                            'V5 201 "Conversation created" Conversation)]
                                     (ResponseForExistedCreated Conversation))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Sem r (ConversationResponse Conversation)
createProteusSelfConversation
    API
  (Named
     "create-self-conversation@v5"
     (Summary "Create a self-conversation"
      :> (From 'V3
          :> (Until 'V6
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("self"
                          :> MultiVerb
                               'POST
                               '[JSON]
                               '[WithHeaders
                                   ConversationHeaders
                                   Conversation
                                   (VersionedRespond 'V5 200 "Conversation existed" Conversation),
                                 WithHeaders
                                   ConversationHeaders
                                   Conversation
                                   (VersionedRespond 'V5 201 "Conversation created" Conversation)]
                               (ResponseForExistedCreated Conversation))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-self-conversation"
        (Summary "Create a self-conversation"
         :> (From 'V6
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("self"
                         :> MultiVerb
                              'POST
                              '[JSON]
                              '[WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V6 200 "Conversation existed" Conversation),
                                WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V6 201 "Conversation created" Conversation)]
                              (ResponseForExistedCreated Conversation))))))
      :<|> (Named
              "get-mls-self-conversation@v5"
              (Summary "Get the user's MLS self-conversation"
               :> (From 'V5
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("mls-self"
                                   :> (CanThrow 'MLSNotEnabled
                                       :> MultiVerb
                                            'GET
                                            '[JSON]
                                            '[VersionedRespond
                                                'V5 200 "The MLS self-conversation" Conversation]
                                            Conversation)))))))
            :<|> (Named
                    "get-mls-self-conversation"
                    (Summary "Get the user's MLS self-conversation"
                     :> (From 'V6
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("mls-self"
                                     :> (CanThrow 'MLSNotEnabled
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200 "The MLS self-conversation" Conversation]
                                              Conversation))))))
                  :<|> (Named
                          "get-subconversation"
                          (Summary "Get information about an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSSubConvUnsupportedConvType
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("subconversations"
                                                               :> (Capture "subconv" SubConvId
                                                                   :> MultiVerb
                                                                        'GET
                                                                        '[JSON]
                                                                        '[Respond
                                                                            200
                                                                            "Subconversation"
                                                                            PublicSubConversation]
                                                                        PublicSubConversation)))))))))))
                        :<|> (Named
                                "leave-subconversation"
                                (Summary "Leave an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'MLSProtocolErrorTag
                                                         :> (CanThrow 'MLSStaleMessage
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (ZLocalUser
                                                                     :> (ZClient
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("subconversations"
                                                                                     :> (Capture
                                                                                           "subconv"
                                                                                           SubConvId
                                                                                         :> ("self"
                                                                                             :> MultiVerb
                                                                                                  'DELETE
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "OK"]
                                                                                                  ()))))))))))))))))
                              :<|> (Named
                                      "delete-subconversation"
                                      (Summary "Delete an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'MLSStaleMessage
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture
                                                                             "cnv" ConvId
                                                                           :> ("subconversations"
                                                                               :> (Capture
                                                                                     "subconv"
                                                                                     SubConvId
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         DeleteSubConversationRequest
                                                                                       :> MultiVerb
                                                                                            'DELETE
                                                                                            '[JSON]
                                                                                            '[Respond
                                                                                                200
                                                                                                "Deletion successful"
                                                                                                ()]
                                                                                            ())))))))))))))
                                    :<|> (Named
                                            "get-subconversation-group-info"
                                            (Summary "Get MLS group information of subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall 'Galley "query-group-info"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'MLSMissingGroupInfo
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture
                                                                               "cnv" ConvId
                                                                             :> ("subconversations"
                                                                                 :> (Capture
                                                                                       "subconv"
                                                                                       SubConvId
                                                                                     :> ("groupinfo"
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[MLS]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "The group information"
                                                                                                  GroupInfoData]
                                                                                              GroupInfoData))))))))))))
                                          :<|> (Named
                                                  "create-one-to-one-conversation@v2"
                                                  (Summary "Create a 1:1 conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-created"
                                                           :> (Until 'V3
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'NoBindingTeamMembers
                                                                           :> (CanThrow
                                                                                 'NonBindingTeam
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         UnreachableBackendsLegacy
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> ("one2one"
                                                                                                                       :> (VersionedReqBody
                                                                                                                             'V2
                                                                                                                             '[JSON]
                                                                                                                             NewConv
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       200
                                                                                                                                       "Conversation existed"
                                                                                                                                       Conversation),
                                                                                                                                  WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       201
                                                                                                                                       "Conversation created"
                                                                                                                                       Conversation)]
                                                                                                                                (ResponseForExistedCreated
                                                                                                                                   Conversation))))))))))))))))))))
                                                :<|> (Named
                                                        "create-one-to-one-conversation"
                                                        (Summary "Create a 1:1 conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-created"
                                                             :> (From 'V3
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'NoBindingTeamMembers
                                                                             :> (CanThrow
                                                                                   'NonBindingTeam
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       'MissingLegalholdConsent
                                                                                                     :> (CanThrow
                                                                                                           UnreachableBackendsLegacy
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("one2one"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               NewConv
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V3
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V3
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         Conversation)]
                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                     Conversation)))))))))))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation@v5"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V5
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> (CanThrow
                                                                                 'MLSNotEnabled
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                       :> ("conversations"
                                                                                           :> ("one2one"
                                                                                               :> (QualifiedCapture
                                                                                                     "usr"
                                                                                                     UserId
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[VersionedRespond
                                                                                                            'V5
                                                                                                            200
                                                                                                            "MLS 1-1 conversation"
                                                                                                            Conversation]
                                                                                                        Conversation))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation@v6"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V6
                                                                         :> (Until 'V7
                                                                             :> (ZLocalUser
                                                                                 :> (CanThrow
                                                                                       'MLSNotEnabled
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> ("conversations"
                                                                                             :> ("one2one"
                                                                                                 :> (QualifiedCapture
                                                                                                       "usr"
                                                                                                       UserId
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "MLS 1-1 conversation"
                                                                                                              (MLSOne2OneConversation
                                                                                                                 MLSPublicKey)]
                                                                                                          (MLSOne2OneConversation
                                                                                                             MLSPublicKey))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V7
                                                                               :> (ZLocalUser
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> ("conversations"
                                                                                               :> ("one2one"
                                                                                                   :> (QualifiedCapture
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> (QueryParam
                                                                                                             "format"
                                                                                                             MLSPublicKeyFormat
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "MLS 1-1 conversation"
                                                                                                                    (MLSOne2OneConversation
                                                                                                                       SomeKey)]
                                                                                                                (MLSOne2OneConversation
                                                                                                                   SomeKey))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation-unqualified"
                                                                                (Summary
                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (Until
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   Invite
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation-unqualified2"
                                                                                      (Summary
                                                                                         "Add qualified members to an existing conversation."
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (Until
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> ("v2"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             InviteQualified
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation"
                                                                                            (Summary
                                                                                               "Add qualified members to an existing conversation."
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (From
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               InviteQualified
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                  (Summary
                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                   :> (Until
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TooManyMembers
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("join"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvJoinResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Join a conversation using a reusable code"
                                                                                                         :> (Description
                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'CodeNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidConversationPassword
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'GuestLinksDisabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TooManyMembers
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("join"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "code-check"
                                                                                                              (Summary
                                                                                                                 "Check validity of a conversation code."
                                                                                                               :> (Description
                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                   :> (CanThrow
                                                                                                                         'CodeNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidConversationPassword
                                                                                                                               :> ("conversations"
                                                                                                                                   :> ("code-check"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationCode
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Valid"]
                                                                                                                                                ()))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                    (Summary
                                                                                                                       "Create or recreate a conversation code"
                                                                                                                     :> (Until
                                                                                                                           'V4
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'WriteConversationsCode
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'GuestLinksDisabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                             :> (ZUser
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Create or recreate a conversation code"
                                                                                                                           :> (From
                                                                                                                                 'V4
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'WriteConversationsCode
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                   :> (ZUser
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                (Summary
                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Delete conversation code"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("code"
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'DELETE
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[Respond
                                                                                                                                                                            200
                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                            Event]
                                                                                                                                                                        Event))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-code"
                                                                                                                                            (Summary
                                                                                                                                               "Get existing conversation code"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'CodeNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'GET
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[Respond
                                                                                                                                                                                          200
                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                ())))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V2
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-member"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-self-conversation@v5"
        (Summary "Create a self-conversation"
         :> (From 'V3
             :> (Until 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("self"
                             :> MultiVerb
                                  'POST
                                  '[JSON]
                                  '[WithHeaders
                                      ConversationHeaders
                                      Conversation
                                      (VersionedRespond
                                         'V5 200 "Conversation existed" Conversation),
                                    WithHeaders
                                      ConversationHeaders
                                      Conversation
                                      (VersionedRespond
                                         'V5 201 "Conversation created" Conversation)]
                                  (ResponseForExistedCreated Conversation)))))))
      :<|> (Named
              "create-self-conversation"
              (Summary "Create a self-conversation"
               :> (From 'V6
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("self"
                               :> MultiVerb
                                    'POST
                                    '[JSON]
                                    '[WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V6 200 "Conversation existed" Conversation),
                                      WithHeaders
                                        ConversationHeaders
                                        Conversation
                                        (VersionedRespond
                                           'V6 201 "Conversation created" Conversation)]
                                    (ResponseForExistedCreated Conversation))))))
            :<|> (Named
                    "get-mls-self-conversation@v5"
                    (Summary "Get the user's MLS self-conversation"
                     :> (From 'V5
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> ("mls-self"
                                         :> (CanThrow 'MLSNotEnabled
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[VersionedRespond
                                                      'V5
                                                      200
                                                      "The MLS self-conversation"
                                                      Conversation]
                                                  Conversation)))))))
                  :<|> (Named
                          "get-mls-self-conversation"
                          (Summary "Get the user's MLS self-conversation"
                           :> (From 'V6
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> ("mls-self"
                                           :> (CanThrow 'MLSNotEnabled
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "The MLS self-conversation"
                                                        Conversation]
                                                    Conversation))))))
                        :<|> (Named
                                "get-subconversation"
                                (Summary "Get information about an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'MLSSubConvUnsupportedConvType
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("subconversations"
                                                                     :> (Capture "subconv" SubConvId
                                                                         :> MultiVerb
                                                                              'GET
                                                                              '[JSON]
                                                                              '[Respond
                                                                                  200
                                                                                  "Subconversation"
                                                                                  PublicSubConversation]
                                                                              PublicSubConversation)))))))))))
                              :<|> (Named
                                      "leave-subconversation"
                                      (Summary "Leave an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall
                                                     'Galley "leave-sub-conversation"
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'MLSProtocolErrorTag
                                                               :> (CanThrow 'MLSStaleMessage
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (ZLocalUser
                                                                           :> (ZClient
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("subconversations"
                                                                                           :> (Capture
                                                                                                 "subconv"
                                                                                                 SubConvId
                                                                                               :> ("self"
                                                                                                   :> MultiVerb
                                                                                                        'DELETE
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "OK"]
                                                                                                        ()))))))))))))))))
                                    :<|> (Named
                                            "delete-subconversation"
                                            (Summary "Delete an MLS subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "delete-sub-conversation"
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (CanThrow 'MLSStaleMessage
                                                                     :> (ZLocalUser
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("subconversations"
                                                                                     :> (Capture
                                                                                           "subconv"
                                                                                           SubConvId
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               DeleteSubConversationRequest
                                                                                             :> MultiVerb
                                                                                                  'DELETE
                                                                                                  '[JSON]
                                                                                                  '[Respond
                                                                                                      200
                                                                                                      "Deletion successful"
                                                                                                      ()]
                                                                                                  ())))))))))))))
                                          :<|> (Named
                                                  "get-subconversation-group-info"
                                                  (Summary
                                                     "Get MLS group information of subconversation"
                                                   :> (From 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "query-group-info"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'MLSMissingGroupInfo
                                                                   :> (CanThrow 'MLSNotEnabled
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture
                                                                                     "cnv" ConvId
                                                                                   :> ("subconversations"
                                                                                       :> (Capture
                                                                                             "subconv"
                                                                                             SubConvId
                                                                                           :> ("groupinfo"
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[MLS]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "The group information"
                                                                                                        GroupInfoData]
                                                                                                    GroupInfoData))))))))))))
                                                :<|> (Named
                                                        "create-one-to-one-conversation@v2"
                                                        (Summary "Create a 1:1 conversation"
                                                         :> (MakesFederatedCall 'Brig "api-version"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-created"
                                                                 :> (Until 'V3
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NoBindingTeamMembers
                                                                                 :> (CanThrow
                                                                                       'NonBindingTeam
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'NotConnected
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               UnreachableBackendsLegacy
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("one2one"
                                                                                                                             :> (VersionedReqBody
                                                                                                                                   'V2
                                                                                                                                   '[JSON]
                                                                                                                                   NewConv
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             200
                                                                                                                                             "Conversation existed"
                                                                                                                                             Conversation),
                                                                                                                                        WithHeaders
                                                                                                                                          ConversationHeaders
                                                                                                                                          Conversation
                                                                                                                                          (VersionedRespond
                                                                                                                                             'V2
                                                                                                                                             201
                                                                                                                                             "Conversation created"
                                                                                                                                             Conversation)]
                                                                                                                                      (ResponseForExistedCreated
                                                                                                                                         Conversation))))))))))))))))))))
                                                      :<|> (Named
                                                              "create-one-to-one-conversation"
                                                              (Summary "Create a 1:1 conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-created"
                                                                   :> (From 'V3
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'NoBindingTeamMembers
                                                                                   :> (CanThrow
                                                                                         'NonBindingTeam
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (CanThrow
                                                                                                             'MissingLegalholdConsent
                                                                                                           :> (CanThrow
                                                                                                                 UnreachableBackendsLegacy
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> ("one2one"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     NewConv
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        '[WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V3
                                                                                                                                               200
                                                                                                                                               "Conversation existed"
                                                                                                                                               Conversation),
                                                                                                                                          WithHeaders
                                                                                                                                            ConversationHeaders
                                                                                                                                            Conversation
                                                                                                                                            (VersionedRespond
                                                                                                                                               'V3
                                                                                                                                               201
                                                                                                                                               "Conversation created"
                                                                                                                                               Conversation)]
                                                                                                                                        (ResponseForExistedCreated
                                                                                                                                           Conversation)))))))))))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation@v5"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V5
                                                                         :> (Until 'V6
                                                                             :> (ZLocalUser
                                                                                 :> (CanThrow
                                                                                       'MLSNotEnabled
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MLSFederatedOne2OneNotSupported
                                                                                             :> ("conversations"
                                                                                                 :> ("one2one"
                                                                                                     :> (QualifiedCapture
                                                                                                           "usr"
                                                                                                           UserId
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[VersionedRespond
                                                                                                                  'V5
                                                                                                                  200
                                                                                                                  "MLS 1-1 conversation"
                                                                                                                  Conversation]
                                                                                                              Conversation))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation@v6"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V6
                                                                               :> (Until 'V7
                                                                                   :> (ZLocalUser
                                                                                       :> (CanThrow
                                                                                             'MLSNotEnabled
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> ("conversations"
                                                                                                   :> ("one2one"
                                                                                                       :> (QualifiedCapture
                                                                                                             "usr"
                                                                                                             UserId
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "MLS 1-1 conversation"
                                                                                                                    (MLSOne2OneConversation
                                                                                                                       MLSPublicKey)]
                                                                                                                (MLSOne2OneConversation
                                                                                                                   MLSPublicKey))))))))))
                                                                        :<|> (Named
                                                                                "get-one-to-one-mls-conversation"
                                                                                (Summary
                                                                                   "Get an MLS 1:1 conversation"
                                                                                 :> (From 'V7
                                                                                     :> (ZLocalUser
                                                                                         :> (CanThrow
                                                                                               'MLSNotEnabled
                                                                                             :> (CanThrow
                                                                                                   'NotConnected
                                                                                                 :> ("conversations"
                                                                                                     :> ("one2one"
                                                                                                         :> (QualifiedCapture
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> (QueryParam
                                                                                                                   "format"
                                                                                                                   MLSPublicKeyFormat
                                                                                                                 :> MultiVerb
                                                                                                                      'GET
                                                                                                                      '[JSON]
                                                                                                                      '[Respond
                                                                                                                          200
                                                                                                                          "MLS 1-1 conversation"
                                                                                                                          (MLSOne2OneConversation
                                                                                                                             SomeKey)]
                                                                                                                      (MLSOne2OneConversation
                                                                                                                         SomeKey))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation-unqualified"
                                                                                      (Summary
                                                                                         "Add members to an existing conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (Until
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         Invite
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation-unqualified2"
                                                                                            (Summary
                                                                                               "Add qualified members to an existing conversation."
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (Until
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> ("v2"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   InviteQualified
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "add-members-to-conversation"
                                                                                                  (Summary
                                                                                                     "Add qualified members to an existing conversation."
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (From
                                                                                                                 'V2
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'AddConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'LeaveConversation)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> (CanThrow
                                                                                                                                     'TooManyMembers
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotConnected
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'MissingLegalholdConsent
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         NonFederatingBackends
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             UnreachableBackends
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     InviteQualified
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'POST
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "join-conversation-by-id-unqualified"
                                                                                                        (Summary
                                                                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                         :> (Until
                                                                                                               'V5
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TooManyMembers
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("join"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvJoinResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "join-conversation-by-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Join a conversation using a reusable code"
                                                                                                               :> (Description
                                                                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'CodeNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidConversationPassword
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'GuestLinksDisabled
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'NotATeamMember
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TooManyMembers
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> ("join"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             JoinConversationByCode
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvJoinResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "code-check"
                                                                                                                    (Summary
                                                                                                                       "Check validity of a conversation code."
                                                                                                                     :> (Description
                                                                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                         :> (CanThrow
                                                                                                                               'CodeNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidConversationPassword
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> ("code-check"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationCode
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Valid"]
                                                                                                                                                      ()))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-conversation-code-unqualified@v3"
                                                                                                                          (Summary
                                                                                                                             "Create or recreate a conversation code"
                                                                                                                           :> (Until
                                                                                                                                 'V4
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'WriteConversationsCode
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                   :> (ZUser
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "create-conversation-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Create or recreate a conversation code"
                                                                                                                                 :> (From
                                                                                                                                       'V4
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'WriteConversationsCode
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'GuestLinksDisabled
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'CreateConversationCodeConflict
                                                                                                                                                         :> (ZUser
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZOptConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-conversation-guest-links-status"
                                                                                                                                      (Summary
                                                                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           GuestLinksConfig)))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-code-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Delete conversation code"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("code"
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'DELETE
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[Respond
                                                                                                                                                                                  200
                                                                                                                                                                                  "Conversation code deleted."
                                                                                                                                                                                  Event]
                                                                                                                                                                              Event))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-code"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get existing conversation code"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'CodeNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'GuestLinksDisabled
                                                                                                                                                                   :> (ZHostOpt
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("code"
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'GET
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[Respond
                                                                                                                                                                                                200
                                                                                                                                                                                                "Conversation Code"
                                                                                                                                                                                                ConversationCodeInfo]
                                                                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "member-typing-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("typing"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'POST
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                                      ())))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "member-typing-qualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Sending typing notifications"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "update-typing-indicator"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("typing"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     TypingStatus
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'POST
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-member-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V2
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "remove-member"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Remove a member from a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "leave-conversation"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-other-member-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-other-member"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update membership of the specified user"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-name"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update conversation name"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-self-conversation" ServerT
  (Summary "Create a self-conversation"
   :> (From 'V6
       :> (ZLocalUser
           :> ("conversations"
               :> ("self"
                   :> MultiVerb
                        'POST
                        '[JSON]
                        '[WithHeaders
                            ConversationHeaders
                            Conversation
                            (VersionedRespond 'V6 200 "Conversation existed" Conversation),
                          WithHeaders
                            ConversationHeaders
                            Conversation
                            (VersionedRespond 'V6 201 "Conversation created" Conversation)]
                        (ResponseForExistedCreated Conversation))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Create a self-conversation"
            :> (From 'V6
                :> (ZLocalUser
                    :> ("conversations"
                        :> ("self"
                            :> MultiVerb
                                 'POST
                                 '[JSON]
                                 '[WithHeaders
                                     ConversationHeaders
                                     Conversation
                                     (VersionedRespond 'V6 200 "Conversation existed" Conversation),
                                   WithHeaders
                                     ConversationHeaders
                                     Conversation
                                     (VersionedRespond 'V6 201 "Conversation created" Conversation)]
                                 (ResponseForExistedCreated Conversation)))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Sem r (ConversationResponse Conversation)
createProteusSelfConversation
    API
  (Named
     "create-self-conversation"
     (Summary "Create a self-conversation"
      :> (From 'V6
          :> (ZLocalUser
              :> ("conversations"
                  :> ("self"
                      :> MultiVerb
                           'POST
                           '[JSON]
                           '[WithHeaders
                               ConversationHeaders
                               Conversation
                               (VersionedRespond 'V6 200 "Conversation existed" Conversation),
                             WithHeaders
                               ConversationHeaders
                               Conversation
                               (VersionedRespond 'V6 201 "Conversation created" Conversation)]
                           (ResponseForExistedCreated Conversation)))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-mls-self-conversation@v5"
        (Summary "Get the user's MLS self-conversation"
         :> (From 'V5
             :> (Until 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("mls-self"
                             :> (CanThrow 'MLSNotEnabled
                                 :> MultiVerb
                                      'GET
                                      '[JSON]
                                      '[VersionedRespond
                                          'V5 200 "The MLS self-conversation" Conversation]
                                      Conversation)))))))
      :<|> (Named
              "get-mls-self-conversation"
              (Summary "Get the user's MLS self-conversation"
               :> (From 'V6
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("mls-self"
                               :> (CanThrow 'MLSNotEnabled
                                   :> MultiVerb
                                        'GET
                                        '[JSON]
                                        '[Respond 200 "The MLS self-conversation" Conversation]
                                        Conversation))))))
            :<|> (Named
                    "get-subconversation"
                    (Summary "Get information about an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "get-sub-conversation"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSSubConvUnsupportedConvType
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("subconversations"
                                                         :> (Capture "subconv" SubConvId
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[Respond
                                                                      200
                                                                      "Subconversation"
                                                                      PublicSubConversation]
                                                                  PublicSubConversation)))))))))))
                  :<|> (Named
                          "leave-subconversation"
                          (Summary "Leave an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'MLSProtocolErrorTag
                                                   :> (CanThrow 'MLSStaleMessage
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> (ZClient
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture
                                                                             "cnv" ConvId
                                                                           :> ("subconversations"
                                                                               :> (Capture
                                                                                     "subconv"
                                                                                     SubConvId
                                                                                   :> ("self"
                                                                                       :> MultiVerb
                                                                                            'DELETE
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "OK"]
                                                                                            ()))))))))))))))))
                        :<|> (Named
                                "delete-subconversation"
                                (Summary "Delete an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'MLSStaleMessage
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture "cnv" ConvId
                                                                     :> ("subconversations"
                                                                         :> (Capture
                                                                               "subconv" SubConvId
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   DeleteSubConversationRequest
                                                                                 :> MultiVerb
                                                                                      'DELETE
                                                                                      '[JSON]
                                                                                      '[Respond
                                                                                          200
                                                                                          "Deletion successful"
                                                                                          ()]
                                                                                      ())))))))))))))
                              :<|> (Named
                                      "get-subconversation-group-info"
                                      (Summary "Get MLS group information of subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "query-group-info"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'MLSMissingGroupInfo
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("subconversations"
                                                                           :> (Capture
                                                                                 "subconv" SubConvId
                                                                               :> ("groupinfo"
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[MLS]
                                                                                        '[Respond
                                                                                            200
                                                                                            "The group information"
                                                                                            GroupInfoData]
                                                                                        GroupInfoData))))))))))))
                                    :<|> (Named
                                            "create-one-to-one-conversation@v2"
                                            (Summary "Create a 1:1 conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-created"
                                                     :> (Until 'V3
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NoBindingTeamMembers
                                                                     :> (CanThrow 'NonBindingTeam
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   UnreachableBackendsLegacy
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> ("one2one"
                                                                                                                 :> (VersionedReqBody
                                                                                                                       'V2
                                                                                                                       '[JSON]
                                                                                                                       NewConv
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 200
                                                                                                                                 "Conversation existed"
                                                                                                                                 Conversation),
                                                                                                                            WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 201
                                                                                                                                 "Conversation created"
                                                                                                                                 Conversation)]
                                                                                                                          (ResponseForExistedCreated
                                                                                                                             Conversation))))))))))))))))))))
                                          :<|> (Named
                                                  "create-one-to-one-conversation"
                                                  (Summary "Create a 1:1 conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-created"
                                                       :> (From 'V3
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow
                                                                         'NoBindingTeamMembers
                                                                       :> (CanThrow 'NonBindingTeam
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 'MissingLegalholdConsent
                                                                                               :> (CanThrow
                                                                                                     UnreachableBackendsLegacy
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> ("one2one"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         NewConv
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V3
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V3
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   Conversation)]
                                                                                                                            (ResponseForExistedCreated
                                                                                                                               Conversation)))))))))))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation@v5"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V5
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> (CanThrow 'MLSNotEnabled
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                 :> ("conversations"
                                                                                     :> ("one2one"
                                                                                         :> (QualifiedCapture
                                                                                               "usr"
                                                                                               UserId
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[VersionedRespond
                                                                                                      'V5
                                                                                                      200
                                                                                                      "MLS 1-1 conversation"
                                                                                                      Conversation]
                                                                                                  Conversation))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation@v6"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V6
                                                                   :> (Until 'V7
                                                                       :> (ZLocalUser
                                                                           :> (CanThrow
                                                                                 'MLSNotEnabled
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> ("conversations"
                                                                                       :> ("one2one"
                                                                                           :> (QualifiedCapture
                                                                                                 "usr"
                                                                                                 UserId
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "MLS 1-1 conversation"
                                                                                                        (MLSOne2OneConversation
                                                                                                           MLSPublicKey)]
                                                                                                    (MLSOne2OneConversation
                                                                                                       MLSPublicKey))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V7
                                                                         :> (ZLocalUser
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> ("conversations"
                                                                                         :> ("one2one"
                                                                                             :> (QualifiedCapture
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> (QueryParam
                                                                                                       "format"
                                                                                                       MLSPublicKeyFormat
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "MLS 1-1 conversation"
                                                                                                              (MLSOne2OneConversation
                                                                                                                 SomeKey)]
                                                                                                          (MLSOne2OneConversation
                                                                                                             SomeKey))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation-unqualified"
                                                                          (Summary
                                                                             "Add members to an existing conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (Until 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             Invite
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation-unqualified2"
                                                                                (Summary
                                                                                   "Add qualified members to an existing conversation."
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (Until
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> ("v2"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       InviteQualified
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation"
                                                                                      (Summary
                                                                                         "Add qualified members to an existing conversation."
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (From
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         InviteQualified
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "join-conversation-by-id-unqualified"
                                                                                            (Summary
                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                             :> (Until
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TooManyMembers
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("join"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvJoinResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Join a conversation using a reusable code"
                                                                                                   :> (Description
                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'CodeNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidConversationPassword
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'GuestLinksDisabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TooManyMembers
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("join"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "code-check"
                                                                                                        (Summary
                                                                                                           "Check validity of a conversation code."
                                                                                                         :> (Description
                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                             :> (CanThrow
                                                                                                                   'CodeNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidConversationPassword
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("code-check"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationCode
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Valid"]
                                                                                                                                          ()))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                              (Summary
                                                                                                                 "Create or recreate a conversation code"
                                                                                                               :> (Until
                                                                                                                     'V4
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'WriteConversationsCode
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'GuestLinksDisabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                       :> (ZUser
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Create or recreate a conversation code"
                                                                                                                     :> (From
                                                                                                                           'V4
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'WriteConversationsCode
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'GuestLinksDisabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                             :> (ZUser
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                          (Summary
                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Delete conversation code"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("code"
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'DELETE
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[Respond
                                                                                                                                                                      200
                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                      Event]
                                                                                                                                                                  Event))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-code"
                                                                                                                                      (Summary
                                                                                                                                         "Get existing conversation code"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'CodeNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'GET
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[Respond
                                                                                                                                                                                    200
                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "member-typing-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Sending typing notifications"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                          ())))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                            ()))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "leave-conversation"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V2
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-member"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-other-member"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-self-conversation"
        (Summary "Create a self-conversation"
         :> (From 'V6
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("self"
                         :> MultiVerb
                              'POST
                              '[JSON]
                              '[WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V6 200 "Conversation existed" Conversation),
                                WithHeaders
                                  ConversationHeaders
                                  Conversation
                                  (VersionedRespond 'V6 201 "Conversation created" Conversation)]
                              (ResponseForExistedCreated Conversation))))))
      :<|> (Named
              "get-mls-self-conversation@v5"
              (Summary "Get the user's MLS self-conversation"
               :> (From 'V5
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> ("conversations"
                               :> ("mls-self"
                                   :> (CanThrow 'MLSNotEnabled
                                       :> MultiVerb
                                            'GET
                                            '[JSON]
                                            '[VersionedRespond
                                                'V5 200 "The MLS self-conversation" Conversation]
                                            Conversation)))))))
            :<|> (Named
                    "get-mls-self-conversation"
                    (Summary "Get the user's MLS self-conversation"
                     :> (From 'V6
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> ("mls-self"
                                     :> (CanThrow 'MLSNotEnabled
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200 "The MLS self-conversation" Conversation]
                                              Conversation))))))
                  :<|> (Named
                          "get-subconversation"
                          (Summary "Get information about an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "get-sub-conversation"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'MLSSubConvUnsupportedConvType
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("subconversations"
                                                               :> (Capture "subconv" SubConvId
                                                                   :> MultiVerb
                                                                        'GET
                                                                        '[JSON]
                                                                        '[Respond
                                                                            200
                                                                            "Subconversation"
                                                                            PublicSubConversation]
                                                                        PublicSubConversation)))))))))))
                        :<|> (Named
                                "leave-subconversation"
                                (Summary "Leave an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'MLSProtocolErrorTag
                                                         :> (CanThrow 'MLSStaleMessage
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (ZLocalUser
                                                                     :> (ZClient
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("subconversations"
                                                                                     :> (Capture
                                                                                           "subconv"
                                                                                           SubConvId
                                                                                         :> ("self"
                                                                                             :> MultiVerb
                                                                                                  'DELETE
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "OK"]
                                                                                                  ()))))))))))))))))
                              :<|> (Named
                                      "delete-subconversation"
                                      (Summary "Delete an MLS subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (CanThrow 'MLSStaleMessage
                                                               :> (ZLocalUser
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture
                                                                             "cnv" ConvId
                                                                           :> ("subconversations"
                                                                               :> (Capture
                                                                                     "subconv"
                                                                                     SubConvId
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         DeleteSubConversationRequest
                                                                                       :> MultiVerb
                                                                                            'DELETE
                                                                                            '[JSON]
                                                                                            '[Respond
                                                                                                200
                                                                                                "Deletion successful"
                                                                                                ()]
                                                                                            ())))))))))))))
                                    :<|> (Named
                                            "get-subconversation-group-info"
                                            (Summary "Get MLS group information of subconversation"
                                             :> (From 'V5
                                                 :> (MakesFederatedCall 'Galley "query-group-info"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'MLSMissingGroupInfo
                                                             :> (CanThrow 'MLSNotEnabled
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture
                                                                               "cnv" ConvId
                                                                             :> ("subconversations"
                                                                                 :> (Capture
                                                                                       "subconv"
                                                                                       SubConvId
                                                                                     :> ("groupinfo"
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[MLS]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "The group information"
                                                                                                  GroupInfoData]
                                                                                              GroupInfoData))))))))))))
                                          :<|> (Named
                                                  "create-one-to-one-conversation@v2"
                                                  (Summary "Create a 1:1 conversation"
                                                   :> (MakesFederatedCall 'Brig "api-version"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-created"
                                                           :> (Until 'V3
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'NoBindingTeamMembers
                                                                           :> (CanThrow
                                                                                 'NonBindingTeam
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'NotConnected
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         UnreachableBackendsLegacy
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> ("one2one"
                                                                                                                       :> (VersionedReqBody
                                                                                                                             'V2
                                                                                                                             '[JSON]
                                                                                                                             NewConv
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       200
                                                                                                                                       "Conversation existed"
                                                                                                                                       Conversation),
                                                                                                                                  WithHeaders
                                                                                                                                    ConversationHeaders
                                                                                                                                    Conversation
                                                                                                                                    (VersionedRespond
                                                                                                                                       'V2
                                                                                                                                       201
                                                                                                                                       "Conversation created"
                                                                                                                                       Conversation)]
                                                                                                                                (ResponseForExistedCreated
                                                                                                                                   Conversation))))))))))))))))))))
                                                :<|> (Named
                                                        "create-one-to-one-conversation"
                                                        (Summary "Create a 1:1 conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-created"
                                                             :> (From 'V3
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'NoBindingTeamMembers
                                                                             :> (CanThrow
                                                                                   'NonBindingTeam
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (CanThrow
                                                                                                       'MissingLegalholdConsent
                                                                                                     :> (CanThrow
                                                                                                           UnreachableBackendsLegacy
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> ("one2one"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               NewConv
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  '[WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V3
                                                                                                                                         200
                                                                                                                                         "Conversation existed"
                                                                                                                                         Conversation),
                                                                                                                                    WithHeaders
                                                                                                                                      ConversationHeaders
                                                                                                                                      Conversation
                                                                                                                                      (VersionedRespond
                                                                                                                                         'V3
                                                                                                                                         201
                                                                                                                                         "Conversation created"
                                                                                                                                         Conversation)]
                                                                                                                                  (ResponseForExistedCreated
                                                                                                                                     Conversation)))))))))))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation@v5"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V5
                                                                   :> (Until 'V6
                                                                       :> (ZLocalUser
                                                                           :> (CanThrow
                                                                                 'MLSNotEnabled
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MLSFederatedOne2OneNotSupported
                                                                                       :> ("conversations"
                                                                                           :> ("one2one"
                                                                                               :> (QualifiedCapture
                                                                                                     "usr"
                                                                                                     UserId
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[VersionedRespond
                                                                                                            'V5
                                                                                                            200
                                                                                                            "MLS 1-1 conversation"
                                                                                                            Conversation]
                                                                                                        Conversation))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation@v6"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V6
                                                                         :> (Until 'V7
                                                                             :> (ZLocalUser
                                                                                 :> (CanThrow
                                                                                       'MLSNotEnabled
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> ("conversations"
                                                                                             :> ("one2one"
                                                                                                 :> (QualifiedCapture
                                                                                                       "usr"
                                                                                                       UserId
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "MLS 1-1 conversation"
                                                                                                              (MLSOne2OneConversation
                                                                                                                 MLSPublicKey)]
                                                                                                          (MLSOne2OneConversation
                                                                                                             MLSPublicKey))))))))))
                                                                  :<|> (Named
                                                                          "get-one-to-one-mls-conversation"
                                                                          (Summary
                                                                             "Get an MLS 1:1 conversation"
                                                                           :> (From 'V7
                                                                               :> (ZLocalUser
                                                                                   :> (CanThrow
                                                                                         'MLSNotEnabled
                                                                                       :> (CanThrow
                                                                                             'NotConnected
                                                                                           :> ("conversations"
                                                                                               :> ("one2one"
                                                                                                   :> (QualifiedCapture
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> (QueryParam
                                                                                                             "format"
                                                                                                             MLSPublicKeyFormat
                                                                                                           :> MultiVerb
                                                                                                                'GET
                                                                                                                '[JSON]
                                                                                                                '[Respond
                                                                                                                    200
                                                                                                                    "MLS 1-1 conversation"
                                                                                                                    (MLSOne2OneConversation
                                                                                                                       SomeKey)]
                                                                                                                (MLSOne2OneConversation
                                                                                                                   SomeKey))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation-unqualified"
                                                                                (Summary
                                                                                   "Add members to an existing conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (Until
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   Invite
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation-unqualified2"
                                                                                      (Summary
                                                                                         "Add qualified members to an existing conversation."
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (Until
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> ("v2"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             InviteQualified
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "add-members-to-conversation"
                                                                                            (Summary
                                                                                               "Add qualified members to an existing conversation."
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (From
                                                                                                           'V2
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'AddConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'LeaveConversation)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> (CanThrow
                                                                                                                               'TooManyMembers
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotConnected
                                                                                                                                         :> (CanThrow
                                                                                                                                               'MissingLegalholdConsent
                                                                                                                                             :> (CanThrow
                                                                                                                                                   NonFederatingBackends
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       UnreachableBackends
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               InviteQualified
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'POST
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "join-conversation-by-id-unqualified"
                                                                                                  (Summary
                                                                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                                   :> (Until
                                                                                                         'V5
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TooManyMembers
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("join"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvJoinResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "join-conversation-by-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Join a conversation using a reusable code"
                                                                                                         :> (Description
                                                                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'CodeNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidConversationPassword
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'GuestLinksDisabled
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'NotATeamMember
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TooManyMembers
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> ("join"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       JoinConversationByCode
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvJoinResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "code-check"
                                                                                                              (Summary
                                                                                                                 "Check validity of a conversation code."
                                                                                                               :> (Description
                                                                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                                   :> (CanThrow
                                                                                                                         'CodeNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidConversationPassword
                                                                                                                               :> ("conversations"
                                                                                                                                   :> ("code-check"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationCode
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Valid"]
                                                                                                                                                ()))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-conversation-code-unqualified@v3"
                                                                                                                    (Summary
                                                                                                                       "Create or recreate a conversation code"
                                                                                                                     :> (Until
                                                                                                                           'V4
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'WriteConversationsCode
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'GuestLinksDisabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                             :> (ZUser
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "create-conversation-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Create or recreate a conversation code"
                                                                                                                           :> (From
                                                                                                                                 'V4
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'WriteConversationsCode
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'GuestLinksDisabled
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'CreateConversationCodeConflict
                                                                                                                                                   :> (ZUser
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZOptConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 CreateConversationCodeRequest
                                                                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-conversation-guest-links-status"
                                                                                                                                (Summary
                                                                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     GuestLinksConfig)))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-code-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Delete conversation code"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("code"
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'DELETE
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[Respond
                                                                                                                                                                            200
                                                                                                                                                                            "Conversation code deleted."
                                                                                                                                                                            Event]
                                                                                                                                                                        Event))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-code"
                                                                                                                                            (Summary
                                                                                                                                               "Get existing conversation code"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'CodeNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'GuestLinksDisabled
                                                                                                                                                             :> (ZHostOpt
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("code"
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'GET
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[Respond
                                                                                                                                                                                          200
                                                                                                                                                                                          "Conversation Code"
                                                                                                                                                                                          ConversationCodeInfo]
                                                                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "member-typing-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "update-typing-indicator"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("typing"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             TypingStatus
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'POST
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                                ())))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "member-typing-qualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Sending typing notifications"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "update-typing-indicator"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("typing"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               TypingStatus
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'POST
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-member-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V2
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "remove-member"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Remove a member from a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "leave-conversation"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-other-member-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-other-member"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update membership of the specified user"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                                                               UserId
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-name"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update conversation name"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                                                                               'V3
                                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-mls-self-conversation@v5" ServerT
  (Summary "Get the user's MLS self-conversation"
   :> (From 'V5
       :> (Until 'V6
           :> (ZLocalUser
               :> ("conversations"
                   :> ("mls-self"
                       :> (CanThrow 'MLSNotEnabled
                           :> MultiVerb
                                'GET
                                '[JSON]
                                '[VersionedRespond
                                    'V5 200 "The MLS self-conversation" Conversation]
                                Conversation)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get the user's MLS self-conversation"
            :> (From 'V5
                :> (Until 'V6
                    :> (ZLocalUser
                        :> ("conversations"
                            :> ("mls-self"
                                :> (CanThrow 'MLSNotEnabled
                                    :> MultiVerb
                                         'GET
                                         '[JSON]
                                         '[VersionedRespond
                                             'V5 200 "The MLS self-conversation" Conversation]
                                         Conversation))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Sem
     '[Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r, Member (Input Env) r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId -> Sem r Conversation
getMLSSelfConversationWithError
    API
  (Named
     "get-mls-self-conversation@v5"
     (Summary "Get the user's MLS self-conversation"
      :> (From 'V5
          :> (Until 'V6
              :> (ZLocalUser
                  :> ("conversations"
                      :> ("mls-self"
                          :> (CanThrow 'MLSNotEnabled
                              :> MultiVerb
                                   'GET
                                   '[JSON]
                                   '[VersionedRespond
                                       'V5 200 "The MLS self-conversation" Conversation]
                                   Conversation))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-mls-self-conversation"
        (Summary "Get the user's MLS self-conversation"
         :> (From 'V6
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("mls-self"
                         :> (CanThrow 'MLSNotEnabled
                             :> MultiVerb
                                  'GET
                                  '[JSON]
                                  '[Respond 200 "The MLS self-conversation" Conversation]
                                  Conversation))))))
      :<|> (Named
              "get-subconversation"
              (Summary "Get information about an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "get-sub-conversation"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'MLSSubConvUnsupportedConvType
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("subconversations"
                                                   :> (Capture "subconv" SubConvId
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[Respond
                                                                200
                                                                "Subconversation"
                                                                PublicSubConversation]
                                                            PublicSubConversation)))))))))))
            :<|> (Named
                    "leave-subconversation"
                    (Summary "Leave an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'MLSProtocolErrorTag
                                             :> (CanThrow 'MLSStaleMessage
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> (ZClient
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture "cnv" ConvId
                                                                     :> ("subconversations"
                                                                         :> (Capture
                                                                               "subconv" SubConvId
                                                                             :> ("self"
                                                                                 :> MultiVerb
                                                                                      'DELETE
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200 "OK"]
                                                                                      ()))))))))))))))))
                  :<|> (Named
                          "delete-subconversation"
                          (Summary "Delete an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'MLSStaleMessage
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> (QualifiedCapture "cnv" ConvId
                                                               :> ("subconversations"
                                                                   :> (Capture "subconv" SubConvId
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             DeleteSubConversationRequest
                                                                           :> MultiVerb
                                                                                'DELETE
                                                                                '[JSON]
                                                                                '[Respond
                                                                                    200
                                                                                    "Deletion successful"
                                                                                    ()]
                                                                                ())))))))))))))
                        :<|> (Named
                                "get-subconversation-group-info"
                                (Summary "Get MLS group information of subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "query-group-info"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'MLSMissingGroupInfo
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("subconversations"
                                                                     :> (Capture "subconv" SubConvId
                                                                         :> ("groupinfo"
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[MLS]
                                                                                  '[Respond
                                                                                      200
                                                                                      "The group information"
                                                                                      GroupInfoData]
                                                                                  GroupInfoData))))))))))))
                              :<|> (Named
                                      "create-one-to-one-conversation@v2"
                                      (Summary "Create a 1:1 conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall 'Galley "on-conversation-created"
                                               :> (Until 'V3
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NoBindingTeamMembers
                                                               :> (CanThrow 'NonBindingTeam
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             UnreachableBackendsLegacy
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> ("one2one"
                                                                                                           :> (VersionedReqBody
                                                                                                                 'V2
                                                                                                                 '[JSON]
                                                                                                                 NewConv
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           200
                                                                                                                           "Conversation existed"
                                                                                                                           Conversation),
                                                                                                                      WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           201
                                                                                                                           "Conversation created"
                                                                                                                           Conversation)]
                                                                                                                    (ResponseForExistedCreated
                                                                                                                       Conversation))))))))))))))))))))
                                    :<|> (Named
                                            "create-one-to-one-conversation"
                                            (Summary "Create a 1:1 conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-created"
                                                 :> (From 'V3
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'NoBindingTeamMembers
                                                                 :> (CanThrow 'NonBindingTeam
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           'MissingLegalholdConsent
                                                                                         :> (CanThrow
                                                                                               UnreachableBackendsLegacy
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> ("one2one"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   NewConv
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V3
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V3
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             Conversation)]
                                                                                                                      (ResponseForExistedCreated
                                                                                                                         Conversation)))))))))))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation@v5"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V5
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> (CanThrow 'MLSNotEnabled
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MLSFederatedOne2OneNotSupported
                                                                           :> ("conversations"
                                                                               :> ("one2one"
                                                                                   :> (QualifiedCapture
                                                                                         "usr"
                                                                                         UserId
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[VersionedRespond
                                                                                                'V5
                                                                                                200
                                                                                                "MLS 1-1 conversation"
                                                                                                Conversation]
                                                                                            Conversation))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation@v6"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V6
                                                             :> (Until 'V7
                                                                 :> (ZLocalUser
                                                                     :> (CanThrow 'MLSNotEnabled
                                                                         :> (CanThrow 'NotConnected
                                                                             :> ("conversations"
                                                                                 :> ("one2one"
                                                                                     :> (QualifiedCapture
                                                                                           "usr"
                                                                                           UserId
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "MLS 1-1 conversation"
                                                                                                  (MLSOne2OneConversation
                                                                                                     MLSPublicKey)]
                                                                                              (MLSOne2OneConversation
                                                                                                 MLSPublicKey))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V7
                                                                   :> (ZLocalUser
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> ("conversations"
                                                                                   :> ("one2one"
                                                                                       :> (QualifiedCapture
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> (QueryParam
                                                                                                 "format"
                                                                                                 MLSPublicKeyFormat
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "MLS 1-1 conversation"
                                                                                                        (MLSOne2OneConversation
                                                                                                           SomeKey)]
                                                                                                    (MLSOne2OneConversation
                                                                                                       SomeKey))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation-unqualified"
                                                                    (Summary
                                                                       "Add members to an existing conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (Until 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       Invite
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation-unqualified2"
                                                                          (Summary
                                                                             "Add qualified members to an existing conversation."
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (Until 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> ("v2"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 InviteQualified
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation"
                                                                                (Summary
                                                                                   "Add qualified members to an existing conversation."
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (From
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   InviteQualified
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "join-conversation-by-id-unqualified"
                                                                                      (Summary
                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                       :> (Until 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TooManyMembers
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("join"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvJoinResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event))))))))))))))
                                                                                    :<|> (Named
                                                                                            "join-conversation-by-code-unqualified"
                                                                                            (Summary
                                                                                               "Join a conversation using a reusable code"
                                                                                             :> (Description
                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (CanThrow
                                                                                                           'CodeNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidConversationPassword
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'GuestLinksDisabled
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TooManyMembers
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("join"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           JoinConversationByCode
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvJoinResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "code-check"
                                                                                                  (Summary
                                                                                                     "Check validity of a conversation code."
                                                                                                   :> (Description
                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                       :> (CanThrow
                                                                                                             'CodeNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidConversationPassword
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("code-check"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationCode
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Valid"]
                                                                                                                                    ()))))))))
                                                                                                :<|> (Named
                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                        (Summary
                                                                                                           "Create or recreate a conversation code"
                                                                                                         :> (Until
                                                                                                               'V4
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'WriteConversationsCode
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'GuestLinksDisabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                 :> (ZUser
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-conversation-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Create or recreate a conversation code"
                                                                                                               :> (From
                                                                                                                     'V4
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'WriteConversationsCode
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'GuestLinksDisabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                       :> (ZUser
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                    (Summary
                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Delete conversation code"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("code"
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'DELETE
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[Respond
                                                                                                                                                                200
                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                Event]
                                                                                                                                                            Event))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-code"
                                                                                                                                (Summary
                                                                                                                                   "Get existing conversation code"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'CodeNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[Respond
                                                                                                                                                                              200
                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "member-typing-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Sending typing notifications"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "update-typing-indicator"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("typing"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 TypingStatus
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                    ())))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "member-typing-qualified"
                                                                                                                                            (Summary
                                                                                                                                               "Sending typing notifications"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("typing"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                      ()))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "leave-conversation"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V2
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                             UserId
                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-member"
                                                                                                                                                        (Summary
                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "leave-conversation"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-other-member"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-mls-self-conversation@v5"
        (Summary "Get the user's MLS self-conversation"
         :> (From 'V5
             :> (Until 'V6
                 :> (ZLocalUser
                     :> ("conversations"
                         :> ("mls-self"
                             :> (CanThrow 'MLSNotEnabled
                                 :> MultiVerb
                                      'GET
                                      '[JSON]
                                      '[VersionedRespond
                                          'V5 200 "The MLS self-conversation" Conversation]
                                      Conversation)))))))
      :<|> (Named
              "get-mls-self-conversation"
              (Summary "Get the user's MLS self-conversation"
               :> (From 'V6
                   :> (ZLocalUser
                       :> ("conversations"
                           :> ("mls-self"
                               :> (CanThrow 'MLSNotEnabled
                                   :> MultiVerb
                                        'GET
                                        '[JSON]
                                        '[Respond 200 "The MLS self-conversation" Conversation]
                                        Conversation))))))
            :<|> (Named
                    "get-subconversation"
                    (Summary "Get information about an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "get-sub-conversation"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'MLSSubConvUnsupportedConvType
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("subconversations"
                                                         :> (Capture "subconv" SubConvId
                                                             :> MultiVerb
                                                                  'GET
                                                                  '[JSON]
                                                                  '[Respond
                                                                      200
                                                                      "Subconversation"
                                                                      PublicSubConversation]
                                                                  PublicSubConversation)))))))))))
                  :<|> (Named
                          "leave-subconversation"
                          (Summary "Leave an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'MLSProtocolErrorTag
                                                   :> (CanThrow 'MLSStaleMessage
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> (ZClient
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture
                                                                             "cnv" ConvId
                                                                           :> ("subconversations"
                                                                               :> (Capture
                                                                                     "subconv"
                                                                                     SubConvId
                                                                                   :> ("self"
                                                                                       :> MultiVerb
                                                                                            'DELETE
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "OK"]
                                                                                            ()))))))))))))))))
                        :<|> (Named
                                "delete-subconversation"
                                (Summary "Delete an MLS subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (CanThrow 'MLSStaleMessage
                                                         :> (ZLocalUser
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture "cnv" ConvId
                                                                     :> ("subconversations"
                                                                         :> (Capture
                                                                               "subconv" SubConvId
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   DeleteSubConversationRequest
                                                                                 :> MultiVerb
                                                                                      'DELETE
                                                                                      '[JSON]
                                                                                      '[Respond
                                                                                          200
                                                                                          "Deletion successful"
                                                                                          ()]
                                                                                      ())))))))))))))
                              :<|> (Named
                                      "get-subconversation-group-info"
                                      (Summary "Get MLS group information of subconversation"
                                       :> (From 'V5
                                           :> (MakesFederatedCall 'Galley "query-group-info"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'MLSMissingGroupInfo
                                                       :> (CanThrow 'MLSNotEnabled
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture "cnv" ConvId
                                                                       :> ("subconversations"
                                                                           :> (Capture
                                                                                 "subconv" SubConvId
                                                                               :> ("groupinfo"
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[MLS]
                                                                                        '[Respond
                                                                                            200
                                                                                            "The group information"
                                                                                            GroupInfoData]
                                                                                        GroupInfoData))))))))))))
                                    :<|> (Named
                                            "create-one-to-one-conversation@v2"
                                            (Summary "Create a 1:1 conversation"
                                             :> (MakesFederatedCall 'Brig "api-version"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-created"
                                                     :> (Until 'V3
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NoBindingTeamMembers
                                                                     :> (CanThrow 'NonBindingTeam
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'NotConnected
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   UnreachableBackendsLegacy
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> ("one2one"
                                                                                                                 :> (VersionedReqBody
                                                                                                                       'V2
                                                                                                                       '[JSON]
                                                                                                                       NewConv
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 200
                                                                                                                                 "Conversation existed"
                                                                                                                                 Conversation),
                                                                                                                            WithHeaders
                                                                                                                              ConversationHeaders
                                                                                                                              Conversation
                                                                                                                              (VersionedRespond
                                                                                                                                 'V2
                                                                                                                                 201
                                                                                                                                 "Conversation created"
                                                                                                                                 Conversation)]
                                                                                                                          (ResponseForExistedCreated
                                                                                                                             Conversation))))))))))))))))))))
                                          :<|> (Named
                                                  "create-one-to-one-conversation"
                                                  (Summary "Create a 1:1 conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-created"
                                                       :> (From 'V3
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow
                                                                         'NoBindingTeamMembers
                                                                       :> (CanThrow 'NonBindingTeam
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (CanThrow
                                                                                                 'MissingLegalholdConsent
                                                                                               :> (CanThrow
                                                                                                     UnreachableBackendsLegacy
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> ("one2one"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         NewConv
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            '[WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V3
                                                                                                                                   200
                                                                                                                                   "Conversation existed"
                                                                                                                                   Conversation),
                                                                                                                              WithHeaders
                                                                                                                                ConversationHeaders
                                                                                                                                Conversation
                                                                                                                                (VersionedRespond
                                                                                                                                   'V3
                                                                                                                                   201
                                                                                                                                   "Conversation created"
                                                                                                                                   Conversation)]
                                                                                                                            (ResponseForExistedCreated
                                                                                                                               Conversation)))))))))))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation@v5"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V5
                                                             :> (Until 'V6
                                                                 :> (ZLocalUser
                                                                     :> (CanThrow 'MLSNotEnabled
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MLSFederatedOne2OneNotSupported
                                                                                 :> ("conversations"
                                                                                     :> ("one2one"
                                                                                         :> (QualifiedCapture
                                                                                               "usr"
                                                                                               UserId
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[VersionedRespond
                                                                                                      'V5
                                                                                                      200
                                                                                                      "MLS 1-1 conversation"
                                                                                                      Conversation]
                                                                                                  Conversation))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation@v6"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V6
                                                                   :> (Until 'V7
                                                                       :> (ZLocalUser
                                                                           :> (CanThrow
                                                                                 'MLSNotEnabled
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> ("conversations"
                                                                                       :> ("one2one"
                                                                                           :> (QualifiedCapture
                                                                                                 "usr"
                                                                                                 UserId
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "MLS 1-1 conversation"
                                                                                                        (MLSOne2OneConversation
                                                                                                           MLSPublicKey)]
                                                                                                    (MLSOne2OneConversation
                                                                                                       MLSPublicKey))))))))))
                                                            :<|> (Named
                                                                    "get-one-to-one-mls-conversation"
                                                                    (Summary
                                                                       "Get an MLS 1:1 conversation"
                                                                     :> (From 'V7
                                                                         :> (ZLocalUser
                                                                             :> (CanThrow
                                                                                   'MLSNotEnabled
                                                                                 :> (CanThrow
                                                                                       'NotConnected
                                                                                     :> ("conversations"
                                                                                         :> ("one2one"
                                                                                             :> (QualifiedCapture
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> (QueryParam
                                                                                                       "format"
                                                                                                       MLSPublicKeyFormat
                                                                                                     :> MultiVerb
                                                                                                          'GET
                                                                                                          '[JSON]
                                                                                                          '[Respond
                                                                                                              200
                                                                                                              "MLS 1-1 conversation"
                                                                                                              (MLSOne2OneConversation
                                                                                                                 SomeKey)]
                                                                                                          (MLSOne2OneConversation
                                                                                                             SomeKey))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation-unqualified"
                                                                          (Summary
                                                                             "Add members to an existing conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (Until 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             Invite
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation-unqualified2"
                                                                                (Summary
                                                                                   "Add qualified members to an existing conversation."
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (Until
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> ("v2"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       InviteQualified
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "add-members-to-conversation"
                                                                                      (Summary
                                                                                         "Add qualified members to an existing conversation."
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (From
                                                                                                     'V2
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'AddConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'LeaveConversation)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> (CanThrow
                                                                                                                         'TooManyMembers
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotConnected
                                                                                                                                   :> (CanThrow
                                                                                                                                         'MissingLegalholdConsent
                                                                                                                                       :> (CanThrow
                                                                                                                                             NonFederatingBackends
                                                                                                                                           :> (CanThrow
                                                                                                                                                 UnreachableBackends
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         InviteQualified
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'POST
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            ConvUpdateResponses
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "join-conversation-by-id-unqualified"
                                                                                            (Summary
                                                                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                             :> (Until
                                                                                                   'V5
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TooManyMembers
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("join"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvJoinResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "join-conversation-by-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Join a conversation using a reusable code"
                                                                                                   :> (Description
                                                                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'CodeNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidConversationPassword
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'GuestLinksDisabled
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'NotATeamMember
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TooManyMembers
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> ("join"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 JoinConversationByCode
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvJoinResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "code-check"
                                                                                                        (Summary
                                                                                                           "Check validity of a conversation code."
                                                                                                         :> (Description
                                                                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                             :> (CanThrow
                                                                                                                   'CodeNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidConversationPassword
                                                                                                                         :> ("conversations"
                                                                                                                             :> ("code-check"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationCode
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Valid"]
                                                                                                                                          ()))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-conversation-code-unqualified@v3"
                                                                                                              (Summary
                                                                                                                 "Create or recreate a conversation code"
                                                                                                               :> (Until
                                                                                                                     'V4
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'WriteConversationsCode
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'GuestLinksDisabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                       :> (ZUser
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "create-conversation-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Create or recreate a conversation code"
                                                                                                                     :> (From
                                                                                                                           'V4
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'WriteConversationsCode
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'GuestLinksDisabled
                                                                                                                                         :> (CanThrow
                                                                                                                                               'CreateConversationCodeConflict
                                                                                                                                             :> (ZUser
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZOptConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           CreateConversationCodeRequest
                                                                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-conversation-guest-links-status"
                                                                                                                          (Summary
                                                                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               GuestLinksConfig)))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-code-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Delete conversation code"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("code"
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'DELETE
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[Respond
                                                                                                                                                                      200
                                                                                                                                                                      "Conversation code deleted."
                                                                                                                                                                      Event]
                                                                                                                                                                  Event))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-code"
                                                                                                                                      (Summary
                                                                                                                                         "Get existing conversation code"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'CodeNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'GuestLinksDisabled
                                                                                                                                                       :> (ZHostOpt
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("code"
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'GET
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[Respond
                                                                                                                                                                                    200
                                                                                                                                                                                    "Conversation Code"
                                                                                                                                                                                    ConversationCodeInfo]
                                                                                                                                                                                ConversationCodeInfo))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "member-typing-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Sending typing notifications"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "update-typing-indicator"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("typing"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       TypingStatus
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'POST
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                                          ())))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "member-typing-qualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Sending typing notifications"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "update-typing-indicator"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-typing-indicator-updated"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("typing"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         TypingStatus
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'POST
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "Notification sent"]
                                                                                                                                                                                            ()))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-member-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "leave-conversation"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V2
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "remove-member"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Remove a member from a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "leave-conversation"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-other-member-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-other-member"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update membership of the specified user"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                                                         UserId
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-name"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update conversation name"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                                                                         'V3
                                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-mls-self-conversation" ServerT
  (Summary "Get the user's MLS self-conversation"
   :> (From 'V6
       :> (ZLocalUser
           :> ("conversations"
               :> ("mls-self"
                   :> (CanThrow 'MLSNotEnabled
                       :> MultiVerb
                            'GET
                            '[JSON]
                            '[Respond 200 "The MLS self-conversation" Conversation]
                            Conversation))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get the user's MLS self-conversation"
            :> (From 'V6
                :> (ZLocalUser
                    :> ("conversations"
                        :> ("mls-self"
                            :> (CanThrow 'MLSNotEnabled
                                :> MultiVerb
                                     'GET
                                     '[JSON]
                                     '[Respond 200 "The MLS self-conversation" Conversation]
                                     Conversation)))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Sem
     '[Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member ConversationStore r, Member (Error InternalError) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r, Member (Input Env) r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId -> Sem r Conversation
getMLSSelfConversationWithError
    API
  (Named
     "get-mls-self-conversation"
     (Summary "Get the user's MLS self-conversation"
      :> (From 'V6
          :> (ZLocalUser
              :> ("conversations"
                  :> ("mls-self"
                      :> (CanThrow 'MLSNotEnabled
                          :> MultiVerb
                               'GET
                               '[JSON]
                               '[Respond 200 "The MLS self-conversation" Conversation]
                               Conversation)))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-subconversation"
        (Summary "Get information about an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "get-sub-conversation"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'MLSSubConvUnsupportedConvType
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("subconversations"
                                             :> (Capture "subconv" SubConvId
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[Respond
                                                          200
                                                          "Subconversation"
                                                          PublicSubConversation]
                                                      PublicSubConversation)))))))))))
      :<|> (Named
              "leave-subconversation"
              (Summary "Leave an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'MLSProtocolErrorTag
                                       :> (CanThrow 'MLSStaleMessage
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> (ZClient
                                                       :> ("conversations"
                                                           :> (QualifiedCapture "cnv" ConvId
                                                               :> ("subconversations"
                                                                   :> (Capture "subconv" SubConvId
                                                                       :> ("self"
                                                                           :> MultiVerb
                                                                                'DELETE
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200 "OK"]
                                                                                ()))))))))))))))))
            :<|> (Named
                    "delete-subconversation"
                    (Summary "Delete an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'MLSStaleMessage
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> (QualifiedCapture "cnv" ConvId
                                                         :> ("subconversations"
                                                             :> (Capture "subconv" SubConvId
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       DeleteSubConversationRequest
                                                                     :> MultiVerb
                                                                          'DELETE
                                                                          '[JSON]
                                                                          '[Respond
                                                                              200
                                                                              "Deletion successful"
                                                                              ()]
                                                                          ())))))))))))))
                  :<|> (Named
                          "get-subconversation-group-info"
                          (Summary "Get MLS group information of subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "query-group-info"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'MLSMissingGroupInfo
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("subconversations"
                                                               :> (Capture "subconv" SubConvId
                                                                   :> ("groupinfo"
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[MLS]
                                                                            '[Respond
                                                                                200
                                                                                "The group information"
                                                                                GroupInfoData]
                                                                            GroupInfoData))))))))))))
                        :<|> (Named
                                "create-one-to-one-conversation@v2"
                                (Summary "Create a 1:1 conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Galley "on-conversation-created"
                                         :> (Until 'V3
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NoBindingTeamMembers
                                                         :> (CanThrow 'NonBindingTeam
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       UnreachableBackendsLegacy
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> ("one2one"
                                                                                                     :> (VersionedReqBody
                                                                                                           'V2
                                                                                                           '[JSON]
                                                                                                           NewConv
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     200
                                                                                                                     "Conversation existed"
                                                                                                                     Conversation),
                                                                                                                WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     201
                                                                                                                     "Conversation created"
                                                                                                                     Conversation)]
                                                                                                              (ResponseForExistedCreated
                                                                                                                 Conversation))))))))))))))))))))
                              :<|> (Named
                                      "create-one-to-one-conversation"
                                      (Summary "Create a 1:1 conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                                           :> (From 'V3
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'NoBindingTeamMembers
                                                           :> (CanThrow 'NonBindingTeam
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     'MissingLegalholdConsent
                                                                                   :> (CanThrow
                                                                                         UnreachableBackendsLegacy
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> ("one2one"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             NewConv
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V3
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V3
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       Conversation)]
                                                                                                                (ResponseForExistedCreated
                                                                                                                   Conversation)))))))))))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation@v5"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V5
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> (CanThrow 'MLSNotEnabled
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MLSFederatedOne2OneNotSupported
                                                                     :> ("conversations"
                                                                         :> ("one2one"
                                                                             :> (QualifiedCapture
                                                                                   "usr" UserId
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[VersionedRespond
                                                                                          'V5
                                                                                          200
                                                                                          "MLS 1-1 conversation"
                                                                                          Conversation]
                                                                                      Conversation))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation@v6"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V6
                                                       :> (Until 'V7
                                                           :> (ZLocalUser
                                                               :> (CanThrow 'MLSNotEnabled
                                                                   :> (CanThrow 'NotConnected
                                                                       :> ("conversations"
                                                                           :> ("one2one"
                                                                               :> (QualifiedCapture
                                                                                     "usr" UserId
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "MLS 1-1 conversation"
                                                                                            (MLSOne2OneConversation
                                                                                               MLSPublicKey)]
                                                                                        (MLSOne2OneConversation
                                                                                           MLSPublicKey))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V7
                                                             :> (ZLocalUser
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> ("conversations"
                                                                             :> ("one2one"
                                                                                 :> (QualifiedCapture
                                                                                       "usr" UserId
                                                                                     :> (QueryParam
                                                                                           "format"
                                                                                           MLSPublicKeyFormat
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "MLS 1-1 conversation"
                                                                                                  (MLSOne2OneConversation
                                                                                                     SomeKey)]
                                                                                              (MLSOne2OneConversation
                                                                                                 SomeKey))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation-unqualified"
                                                              (Summary
                                                                 "Add members to an existing conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (Until 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 Invite
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation-unqualified2"
                                                                    (Summary
                                                                       "Add qualified members to an existing conversation."
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (Until 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> ("v2"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           InviteQualified
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation"
                                                                          (Summary
                                                                             "Add qualified members to an existing conversation."
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (From 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             InviteQualified
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "join-conversation-by-id-unqualified"
                                                                                (Summary
                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                 :> (Until 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TooManyMembers
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("join"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvJoinResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event))))))))))))))
                                                                              :<|> (Named
                                                                                      "join-conversation-by-code-unqualified"
                                                                                      (Summary
                                                                                         "Join a conversation using a reusable code"
                                                                                       :> (Description
                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (CanThrow
                                                                                                     'CodeNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidConversationPassword
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'GuestLinksDisabled
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TooManyMembers
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("join"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     JoinConversationByCode
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvJoinResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "code-check"
                                                                                            (Summary
                                                                                               "Check validity of a conversation code."
                                                                                             :> (Description
                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                 :> (CanThrow
                                                                                                       'CodeNotFound
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidConversationPassword
                                                                                                             :> ("conversations"
                                                                                                                 :> ("code-check"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationCode
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Valid"]
                                                                                                                              ()))))))))
                                                                                          :<|> (Named
                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                  (Summary
                                                                                                     "Create or recreate a conversation code"
                                                                                                   :> (Until
                                                                                                         'V4
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'WriteConversationsCode
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'GuestLinksDisabled
                                                                                                                       :> (CanThrow
                                                                                                                             'CreateConversationCodeConflict
                                                                                                                           :> (ZUser
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-conversation-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Create or recreate a conversation code"
                                                                                                         :> (From
                                                                                                               'V4
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'WriteConversationsCode
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'GuestLinksDisabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                 :> (ZUser
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-conversation-guest-links-status"
                                                                                                              (Summary
                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Delete conversation code"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("code"
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'DELETE
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[Respond
                                                                                                                                                          200
                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                          Event]
                                                                                                                                                      Event))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-code"
                                                                                                                          (Summary
                                                                                                                             "Get existing conversation code"
                                                                                                                           :> (CanThrow
                                                                                                                                 'CodeNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'GuestLinksDisabled
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[Respond
                                                                                                                                                                        200
                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "member-typing-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Sending typing notifications"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "update-typing-indicator"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("typing"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           TypingStatus
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                              ())))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "member-typing-qualified"
                                                                                                                                      (Summary
                                                                                                                                         "Sending typing notifications"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "update-typing-indicator"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("typing"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             TypingStatus
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                ()))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-member-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "leave-conversation"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V2
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                       UserId
                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-member"
                                                                                                                                                  (Summary
                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "leave-conversation"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-other-member"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-mls-self-conversation"
        (Summary "Get the user's MLS self-conversation"
         :> (From 'V6
             :> (ZLocalUser
                 :> ("conversations"
                     :> ("mls-self"
                         :> (CanThrow 'MLSNotEnabled
                             :> MultiVerb
                                  'GET
                                  '[JSON]
                                  '[Respond 200 "The MLS self-conversation" Conversation]
                                  Conversation))))))
      :<|> (Named
              "get-subconversation"
              (Summary "Get information about an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "get-sub-conversation"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'MLSSubConvUnsupportedConvType
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("subconversations"
                                                   :> (Capture "subconv" SubConvId
                                                       :> MultiVerb
                                                            'GET
                                                            '[JSON]
                                                            '[Respond
                                                                200
                                                                "Subconversation"
                                                                PublicSubConversation]
                                                            PublicSubConversation)))))))))))
            :<|> (Named
                    "leave-subconversation"
                    (Summary "Leave an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'MLSProtocolErrorTag
                                             :> (CanThrow 'MLSStaleMessage
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> (ZClient
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture "cnv" ConvId
                                                                     :> ("subconversations"
                                                                         :> (Capture
                                                                               "subconv" SubConvId
                                                                             :> ("self"
                                                                                 :> MultiVerb
                                                                                      'DELETE
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200 "OK"]
                                                                                      ()))))))))))))))))
                  :<|> (Named
                          "delete-subconversation"
                          (Summary "Delete an MLS subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (CanThrow 'MLSStaleMessage
                                                   :> (ZLocalUser
                                                       :> ("conversations"
                                                           :> (QualifiedCapture "cnv" ConvId
                                                               :> ("subconversations"
                                                                   :> (Capture "subconv" SubConvId
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             DeleteSubConversationRequest
                                                                           :> MultiVerb
                                                                                'DELETE
                                                                                '[JSON]
                                                                                '[Respond
                                                                                    200
                                                                                    "Deletion successful"
                                                                                    ()]
                                                                                ())))))))))))))
                        :<|> (Named
                                "get-subconversation-group-info"
                                (Summary "Get MLS group information of subconversation"
                                 :> (From 'V5
                                     :> (MakesFederatedCall 'Galley "query-group-info"
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'MLSMissingGroupInfo
                                                 :> (CanThrow 'MLSNotEnabled
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (QualifiedCapture "cnv" ConvId
                                                                 :> ("subconversations"
                                                                     :> (Capture "subconv" SubConvId
                                                                         :> ("groupinfo"
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[MLS]
                                                                                  '[Respond
                                                                                      200
                                                                                      "The group information"
                                                                                      GroupInfoData]
                                                                                  GroupInfoData))))))))))))
                              :<|> (Named
                                      "create-one-to-one-conversation@v2"
                                      (Summary "Create a 1:1 conversation"
                                       :> (MakesFederatedCall 'Brig "api-version"
                                           :> (MakesFederatedCall 'Galley "on-conversation-created"
                                               :> (Until 'V3
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NoBindingTeamMembers
                                                               :> (CanThrow 'NonBindingTeam
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'NotConnected
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             UnreachableBackendsLegacy
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> ("one2one"
                                                                                                           :> (VersionedReqBody
                                                                                                                 'V2
                                                                                                                 '[JSON]
                                                                                                                 NewConv
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           200
                                                                                                                           "Conversation existed"
                                                                                                                           Conversation),
                                                                                                                      WithHeaders
                                                                                                                        ConversationHeaders
                                                                                                                        Conversation
                                                                                                                        (VersionedRespond
                                                                                                                           'V2
                                                                                                                           201
                                                                                                                           "Conversation created"
                                                                                                                           Conversation)]
                                                                                                                    (ResponseForExistedCreated
                                                                                                                       Conversation))))))))))))))))))))
                                    :<|> (Named
                                            "create-one-to-one-conversation"
                                            (Summary "Create a 1:1 conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-created"
                                                 :> (From 'V3
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'NoBindingTeamMembers
                                                                 :> (CanThrow 'NonBindingTeam
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (CanThrow
                                                                                           'MissingLegalholdConsent
                                                                                         :> (CanThrow
                                                                                               UnreachableBackendsLegacy
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> ("one2one"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   NewConv
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      '[WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V3
                                                                                                                             200
                                                                                                                             "Conversation existed"
                                                                                                                             Conversation),
                                                                                                                        WithHeaders
                                                                                                                          ConversationHeaders
                                                                                                                          Conversation
                                                                                                                          (VersionedRespond
                                                                                                                             'V3
                                                                                                                             201
                                                                                                                             "Conversation created"
                                                                                                                             Conversation)]
                                                                                                                      (ResponseForExistedCreated
                                                                                                                         Conversation)))))))))))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation@v5"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V5
                                                       :> (Until 'V6
                                                           :> (ZLocalUser
                                                               :> (CanThrow 'MLSNotEnabled
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MLSFederatedOne2OneNotSupported
                                                                           :> ("conversations"
                                                                               :> ("one2one"
                                                                                   :> (QualifiedCapture
                                                                                         "usr"
                                                                                         UserId
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[VersionedRespond
                                                                                                'V5
                                                                                                200
                                                                                                "MLS 1-1 conversation"
                                                                                                Conversation]
                                                                                            Conversation))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation@v6"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V6
                                                             :> (Until 'V7
                                                                 :> (ZLocalUser
                                                                     :> (CanThrow 'MLSNotEnabled
                                                                         :> (CanThrow 'NotConnected
                                                                             :> ("conversations"
                                                                                 :> ("one2one"
                                                                                     :> (QualifiedCapture
                                                                                           "usr"
                                                                                           UserId
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "MLS 1-1 conversation"
                                                                                                  (MLSOne2OneConversation
                                                                                                     MLSPublicKey)]
                                                                                              (MLSOne2OneConversation
                                                                                                 MLSPublicKey))))))))))
                                                      :<|> (Named
                                                              "get-one-to-one-mls-conversation"
                                                              (Summary "Get an MLS 1:1 conversation"
                                                               :> (From 'V7
                                                                   :> (ZLocalUser
                                                                       :> (CanThrow 'MLSNotEnabled
                                                                           :> (CanThrow
                                                                                 'NotConnected
                                                                               :> ("conversations"
                                                                                   :> ("one2one"
                                                                                       :> (QualifiedCapture
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> (QueryParam
                                                                                                 "format"
                                                                                                 MLSPublicKeyFormat
                                                                                               :> MultiVerb
                                                                                                    'GET
                                                                                                    '[JSON]
                                                                                                    '[Respond
                                                                                                        200
                                                                                                        "MLS 1-1 conversation"
                                                                                                        (MLSOne2OneConversation
                                                                                                           SomeKey)]
                                                                                                    (MLSOne2OneConversation
                                                                                                       SomeKey))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation-unqualified"
                                                                    (Summary
                                                                       "Add members to an existing conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (Until 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       Invite
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation-unqualified2"
                                                                          (Summary
                                                                             "Add qualified members to an existing conversation."
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (Until 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> ("v2"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 InviteQualified
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "add-members-to-conversation"
                                                                                (Summary
                                                                                   "Add qualified members to an existing conversation."
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (From
                                                                                               'V2
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'AddConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'LeaveConversation)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> (CanThrow
                                                                                                                   'TooManyMembers
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'NotConnected
                                                                                                                             :> (CanThrow
                                                                                                                                   'MissingLegalholdConsent
                                                                                                                                 :> (CanThrow
                                                                                                                                       NonFederatingBackends
                                                                                                                                     :> (CanThrow
                                                                                                                                           UnreachableBackends
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   InviteQualified
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'POST
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      ConvUpdateResponses
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "join-conversation-by-id-unqualified"
                                                                                      (Summary
                                                                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                       :> (Until 'V5
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TooManyMembers
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("join"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvJoinResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event))))))))))))))
                                                                                    :<|> (Named
                                                                                            "join-conversation-by-code-unqualified"
                                                                                            (Summary
                                                                                               "Join a conversation using a reusable code"
                                                                                             :> (Description
                                                                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (CanThrow
                                                                                                           'CodeNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidConversationPassword
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'GuestLinksDisabled
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'NotATeamMember
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TooManyMembers
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> ("join"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           JoinConversationByCode
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvJoinResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "code-check"
                                                                                                  (Summary
                                                                                                     "Check validity of a conversation code."
                                                                                                   :> (Description
                                                                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                       :> (CanThrow
                                                                                                             'CodeNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidConversationPassword
                                                                                                                   :> ("conversations"
                                                                                                                       :> ("code-check"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationCode
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Valid"]
                                                                                                                                    ()))))))))
                                                                                                :<|> (Named
                                                                                                        "create-conversation-code-unqualified@v3"
                                                                                                        (Summary
                                                                                                           "Create or recreate a conversation code"
                                                                                                         :> (Until
                                                                                                               'V4
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'WriteConversationsCode
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'GuestLinksDisabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                 :> (ZUser
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "create-conversation-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Create or recreate a conversation code"
                                                                                                               :> (From
                                                                                                                     'V4
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'WriteConversationsCode
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'GuestLinksDisabled
                                                                                                                                   :> (CanThrow
                                                                                                                                         'CreateConversationCodeConflict
                                                                                                                                       :> (ZUser
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZOptConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     CreateConversationCodeRequest
                                                                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-conversation-guest-links-status"
                                                                                                                    (Summary
                                                                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         GuestLinksConfig)))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-code-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Delete conversation code"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("code"
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'DELETE
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[Respond
                                                                                                                                                                200
                                                                                                                                                                "Conversation code deleted."
                                                                                                                                                                Event]
                                                                                                                                                            Event))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-code"
                                                                                                                                (Summary
                                                                                                                                   "Get existing conversation code"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'CodeNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'GuestLinksDisabled
                                                                                                                                                 :> (ZHostOpt
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("code"
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'GET
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[Respond
                                                                                                                                                                              200
                                                                                                                                                                              "Conversation Code"
                                                                                                                                                                              ConversationCodeInfo]
                                                                                                                                                                          ConversationCodeInfo))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "member-typing-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Sending typing notifications"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "update-typing-indicator"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("typing"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 TypingStatus
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'POST
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                                    ())))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "member-typing-qualified"
                                                                                                                                            (Summary
                                                                                                                                               "Sending typing notifications"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "update-typing-indicator"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-typing-indicator-updated"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("typing"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   TypingStatus
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'POST
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "Notification sent"]
                                                                                                                                                                                      ()))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-member-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "leave-conversation"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V2
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                             UserId
                                                                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "remove-member"
                                                                                                                                                        (Summary
                                                                                                                                                           "Remove a member from a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "leave-conversation"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-other-member-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-other-member"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update membership of the specified user"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                                                   UserId
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-name"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update conversation name"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                                                             :> (From
                                                                                                                                                                                                                                                   'V3
                                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                                                                              'V5
                                                                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-subconversation" (((HasAnnotation 'Remote "galley" "get-sub-conversation",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> SubConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'MLSSubConvUnsupportedConvType ()), BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      PublicSubConversation)
-> Dict (HasAnnotation 'Remote "galley" "get-sub-conversation")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSSubConvUnsupportedConvType ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     PublicSubConversation
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "get-sub-conversation",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSSubConvUnsupportedConvType ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     PublicSubConversation
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'MLSSubConvUnsupportedConvType ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     PublicSubConversation
forall (r :: EffectRow).
Members
  '[SubConversationStore, ConversationStore,
    Error (Tagged 'ConvNotFound ()),
    Error (Tagged 'ConvAccessDenied ()),
    Error (Tagged 'MLSSubConvUnsupportedConvType ()),
    Error FederationError, FederatorAccess]
  r =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> SubConvId -> Sem r PublicSubConversation
getSubConversation)
    API
  (Named
     "get-subconversation"
     (Summary "Get information about an MLS subconversation"
      :> (From 'V5
          :> (MakesFederatedCall 'Galley "get-sub-conversation"
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'ConvAccessDenied
                      :> (CanThrow 'MLSSubConvUnsupportedConvType
                          :> (ZLocalUser
                              :> ("conversations"
                                  :> (QualifiedCapture "cnv" ConvId
                                      :> ("subconversations"
                                          :> (Capture "subconv" SubConvId
                                              :> MultiVerb
                                                   'GET
                                                   '[JSON]
                                                   '[Respond
                                                       200 "Subconversation" PublicSubConversation]
                                                   PublicSubConversation))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "leave-subconversation"
        (Summary "Leave an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'MLSProtocolErrorTag
                                 :> (CanThrow 'MLSStaleMessage
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> (ZClient
                                                 :> ("conversations"
                                                     :> (QualifiedCapture "cnv" ConvId
                                                         :> ("subconversations"
                                                             :> (Capture "subconv" SubConvId
                                                                 :> ("self"
                                                                     :> MultiVerb
                                                                          'DELETE
                                                                          '[JSON]
                                                                          '[RespondEmpty 200 "OK"]
                                                                          ()))))))))))))))))
      :<|> (Named
              "delete-subconversation"
              (Summary "Delete an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'MLSNotEnabled
                                   :> (CanThrow 'MLSStaleMessage
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> (QualifiedCapture "cnv" ConvId
                                                   :> ("subconversations"
                                                       :> (Capture "subconv" SubConvId
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 DeleteSubConversationRequest
                                                               :> MultiVerb
                                                                    'DELETE
                                                                    '[JSON]
                                                                    '[Respond
                                                                        200
                                                                        "Deletion successful"
                                                                        ()]
                                                                    ())))))))))))))
            :<|> (Named
                    "get-subconversation-group-info"
                    (Summary "Get MLS group information of subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "query-group-info"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'MLSMissingGroupInfo
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("subconversations"
                                                         :> (Capture "subconv" SubConvId
                                                             :> ("groupinfo"
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[MLS]
                                                                      '[Respond
                                                                          200
                                                                          "The group information"
                                                                          GroupInfoData]
                                                                      GroupInfoData))))))))))))
                  :<|> (Named
                          "create-one-to-one-conversation@v2"
                          (Summary "Create a 1:1 conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Galley "on-conversation-created"
                                   :> (Until 'V3
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NoBindingTeamMembers
                                                   :> (CanThrow 'NonBindingTeam
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 UnreachableBackendsLegacy
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> ("one2one"
                                                                                               :> (VersionedReqBody
                                                                                                     'V2
                                                                                                     '[JSON]
                                                                                                     NewConv
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               200
                                                                                                               "Conversation existed"
                                                                                                               Conversation),
                                                                                                          WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               201
                                                                                                               "Conversation created"
                                                                                                               Conversation)]
                                                                                                        (ResponseForExistedCreated
                                                                                                           Conversation))))))))))))))))))))
                        :<|> (Named
                                "create-one-to-one-conversation"
                                (Summary "Create a 1:1 conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                                     :> (From 'V3
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'NoBindingTeamMembers
                                                     :> (CanThrow 'NonBindingTeam
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               'MissingLegalholdConsent
                                                                             :> (CanThrow
                                                                                   UnreachableBackendsLegacy
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> ("one2one"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       NewConv
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V3
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V3
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 Conversation)]
                                                                                                          (ResponseForExistedCreated
                                                                                                             Conversation)))))))))))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation@v5"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V5
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> (CanThrow 'MLSNotEnabled
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow
                                                                 'MLSFederatedOne2OneNotSupported
                                                               :> ("conversations"
                                                                   :> ("one2one"
                                                                       :> (QualifiedCapture
                                                                             "usr" UserId
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[VersionedRespond
                                                                                    'V5
                                                                                    200
                                                                                    "MLS 1-1 conversation"
                                                                                    Conversation]
                                                                                Conversation))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation@v6"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V6
                                                 :> (Until 'V7
                                                     :> (ZLocalUser
                                                         :> (CanThrow 'MLSNotEnabled
                                                             :> (CanThrow 'NotConnected
                                                                 :> ("conversations"
                                                                     :> ("one2one"
                                                                         :> (QualifiedCapture
                                                                               "usr" UserId
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "MLS 1-1 conversation"
                                                                                      (MLSOne2OneConversation
                                                                                         MLSPublicKey)]
                                                                                  (MLSOne2OneConversation
                                                                                     MLSPublicKey))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V7
                                                       :> (ZLocalUser
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> ("conversations"
                                                                       :> ("one2one"
                                                                           :> (QualifiedCapture
                                                                                 "usr" UserId
                                                                               :> (QueryParam
                                                                                     "format"
                                                                                     MLSPublicKeyFormat
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "MLS 1-1 conversation"
                                                                                            (MLSOne2OneConversation
                                                                                               SomeKey)]
                                                                                        (MLSOne2OneConversation
                                                                                           SomeKey))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation-unqualified"
                                                        (Summary
                                                           "Add members to an existing conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (Until 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           Invite
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              ConvUpdateResponses
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation-unqualified2"
                                                              (Summary
                                                                 "Add qualified members to an existing conversation."
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (Until 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> ("v2"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     InviteQualified
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation"
                                                                    (Summary
                                                                       "Add qualified members to an existing conversation."
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (From 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       InviteQualified
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "join-conversation-by-id-unqualified"
                                                                          (Summary
                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                           :> (Until 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TooManyMembers
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("join"
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvJoinResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event))))))))))))))
                                                                        :<|> (Named
                                                                                "join-conversation-by-code-unqualified"
                                                                                (Summary
                                                                                   "Join a conversation using a reusable code"
                                                                                 :> (Description
                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (CanThrow
                                                                                               'CodeNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidConversationPassword
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'GuestLinksDisabled
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TooManyMembers
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("join"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               JoinConversationByCode
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvJoinResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))
                                                                              :<|> (Named
                                                                                      "code-check"
                                                                                      (Summary
                                                                                         "Check validity of a conversation code."
                                                                                       :> (Description
                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                           :> (CanThrow
                                                                                                 'CodeNotFound
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidConversationPassword
                                                                                                       :> ("conversations"
                                                                                                           :> ("code-check"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationCode
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Valid"]
                                                                                                                        ()))))))))
                                                                                    :<|> (Named
                                                                                            "create-conversation-code-unqualified@v3"
                                                                                            (Summary
                                                                                               "Create or recreate a conversation code"
                                                                                             :> (Until
                                                                                                   'V4
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'WriteConversationsCode
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'CreateConversationCodeConflict
                                                                                                                     :> (ZUser
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-conversation-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Create or recreate a conversation code"
                                                                                                   :> (From
                                                                                                         'V4
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'WriteConversationsCode
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'GuestLinksDisabled
                                                                                                                       :> (CanThrow
                                                                                                                             'CreateConversationCodeConflict
                                                                                                                           :> (ZUser
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-conversation-guest-links-status"
                                                                                                        (Summary
                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Delete conversation code"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("code"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'DELETE
                                                                                                                                                '[JSON]
                                                                                                                                                '[Respond
                                                                                                                                                    200
                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                    Event]
                                                                                                                                                Event))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-code"
                                                                                                                    (Summary
                                                                                                                       "Get existing conversation code"
                                                                                                                     :> (CanThrow
                                                                                                                           'CodeNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'GuestLinksDisabled
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[Respond
                                                                                                                                                                  200
                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "member-typing-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Sending typing notifications"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "update-typing-indicator"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("typing"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     TypingStatus
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                        ())))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "member-typing-qualified"
                                                                                                                                (Summary
                                                                                                                                   "Sending typing notifications"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "update-typing-indicator"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("typing"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       TypingStatus
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                          ()))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-member-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "leave-conversation"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (Until
                                                                                                                                                             'V2
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                 UserId
                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-member"
                                                                                                                                            (Summary
                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "leave-conversation"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-other-member"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                         :> (Description
                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-subconversation"
        (Summary "Get information about an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "get-sub-conversation"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'MLSSubConvUnsupportedConvType
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("subconversations"
                                             :> (Capture "subconv" SubConvId
                                                 :> MultiVerb
                                                      'GET
                                                      '[JSON]
                                                      '[Respond
                                                          200
                                                          "Subconversation"
                                                          PublicSubConversation]
                                                      PublicSubConversation)))))))))))
      :<|> (Named
              "leave-subconversation"
              (Summary "Leave an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'MLSProtocolErrorTag
                                       :> (CanThrow 'MLSStaleMessage
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> (ZClient
                                                       :> ("conversations"
                                                           :> (QualifiedCapture "cnv" ConvId
                                                               :> ("subconversations"
                                                                   :> (Capture "subconv" SubConvId
                                                                       :> ("self"
                                                                           :> MultiVerb
                                                                                'DELETE
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200 "OK"]
                                                                                ()))))))))))))))))
            :<|> (Named
                    "delete-subconversation"
                    (Summary "Delete an MLS subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (CanThrow 'MLSStaleMessage
                                             :> (ZLocalUser
                                                 :> ("conversations"
                                                     :> (QualifiedCapture "cnv" ConvId
                                                         :> ("subconversations"
                                                             :> (Capture "subconv" SubConvId
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       DeleteSubConversationRequest
                                                                     :> MultiVerb
                                                                          'DELETE
                                                                          '[JSON]
                                                                          '[Respond
                                                                              200
                                                                              "Deletion successful"
                                                                              ()]
                                                                          ())))))))))))))
                  :<|> (Named
                          "get-subconversation-group-info"
                          (Summary "Get MLS group information of subconversation"
                           :> (From 'V5
                               :> (MakesFederatedCall 'Galley "query-group-info"
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'MLSMissingGroupInfo
                                           :> (CanThrow 'MLSNotEnabled
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (QualifiedCapture "cnv" ConvId
                                                           :> ("subconversations"
                                                               :> (Capture "subconv" SubConvId
                                                                   :> ("groupinfo"
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[MLS]
                                                                            '[Respond
                                                                                200
                                                                                "The group information"
                                                                                GroupInfoData]
                                                                            GroupInfoData))))))))))))
                        :<|> (Named
                                "create-one-to-one-conversation@v2"
                                (Summary "Create a 1:1 conversation"
                                 :> (MakesFederatedCall 'Brig "api-version"
                                     :> (MakesFederatedCall 'Galley "on-conversation-created"
                                         :> (Until 'V3
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NoBindingTeamMembers
                                                         :> (CanThrow 'NonBindingTeam
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'NotConnected
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       UnreachableBackendsLegacy
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> ("one2one"
                                                                                                     :> (VersionedReqBody
                                                                                                           'V2
                                                                                                           '[JSON]
                                                                                                           NewConv
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     200
                                                                                                                     "Conversation existed"
                                                                                                                     Conversation),
                                                                                                                WithHeaders
                                                                                                                  ConversationHeaders
                                                                                                                  Conversation
                                                                                                                  (VersionedRespond
                                                                                                                     'V2
                                                                                                                     201
                                                                                                                     "Conversation created"
                                                                                                                     Conversation)]
                                                                                                              (ResponseForExistedCreated
                                                                                                                 Conversation))))))))))))))))))))
                              :<|> (Named
                                      "create-one-to-one-conversation"
                                      (Summary "Create a 1:1 conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-created"
                                           :> (From 'V3
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'NoBindingTeamMembers
                                                           :> (CanThrow 'NonBindingTeam
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (CanThrow
                                                                                     'MissingLegalholdConsent
                                                                                   :> (CanThrow
                                                                                         UnreachableBackendsLegacy
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> ("one2one"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             NewConv
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                '[WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V3
                                                                                                                       200
                                                                                                                       "Conversation existed"
                                                                                                                       Conversation),
                                                                                                                  WithHeaders
                                                                                                                    ConversationHeaders
                                                                                                                    Conversation
                                                                                                                    (VersionedRespond
                                                                                                                       'V3
                                                                                                                       201
                                                                                                                       "Conversation created"
                                                                                                                       Conversation)]
                                                                                                                (ResponseForExistedCreated
                                                                                                                   Conversation)))))))))))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation@v5"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V5
                                                 :> (Until 'V6
                                                     :> (ZLocalUser
                                                         :> (CanThrow 'MLSNotEnabled
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MLSFederatedOne2OneNotSupported
                                                                     :> ("conversations"
                                                                         :> ("one2one"
                                                                             :> (QualifiedCapture
                                                                                   "usr" UserId
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[VersionedRespond
                                                                                          'V5
                                                                                          200
                                                                                          "MLS 1-1 conversation"
                                                                                          Conversation]
                                                                                      Conversation))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation@v6"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V6
                                                       :> (Until 'V7
                                                           :> (ZLocalUser
                                                               :> (CanThrow 'MLSNotEnabled
                                                                   :> (CanThrow 'NotConnected
                                                                       :> ("conversations"
                                                                           :> ("one2one"
                                                                               :> (QualifiedCapture
                                                                                     "usr" UserId
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "MLS 1-1 conversation"
                                                                                            (MLSOne2OneConversation
                                                                                               MLSPublicKey)]
                                                                                        (MLSOne2OneConversation
                                                                                           MLSPublicKey))))))))))
                                                :<|> (Named
                                                        "get-one-to-one-mls-conversation"
                                                        (Summary "Get an MLS 1:1 conversation"
                                                         :> (From 'V7
                                                             :> (ZLocalUser
                                                                 :> (CanThrow 'MLSNotEnabled
                                                                     :> (CanThrow 'NotConnected
                                                                         :> ("conversations"
                                                                             :> ("one2one"
                                                                                 :> (QualifiedCapture
                                                                                       "usr" UserId
                                                                                     :> (QueryParam
                                                                                           "format"
                                                                                           MLSPublicKeyFormat
                                                                                         :> MultiVerb
                                                                                              'GET
                                                                                              '[JSON]
                                                                                              '[Respond
                                                                                                  200
                                                                                                  "MLS 1-1 conversation"
                                                                                                  (MLSOne2OneConversation
                                                                                                     SomeKey)]
                                                                                              (MLSOne2OneConversation
                                                                                                 SomeKey))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation-unqualified"
                                                              (Summary
                                                                 "Add members to an existing conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (Until 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 Invite
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation-unqualified2"
                                                                    (Summary
                                                                       "Add qualified members to an existing conversation."
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (Until 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> ("v2"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           InviteQualified
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              ConvUpdateResponses
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "add-members-to-conversation"
                                                                          (Summary
                                                                             "Add qualified members to an existing conversation."
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (From 'V2
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'AddConversationMember)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'LeaveConversation)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> (CanThrow
                                                                                                             'TooManyMembers
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'NotConnected
                                                                                                                       :> (CanThrow
                                                                                                                             'MissingLegalholdConsent
                                                                                                                           :> (CanThrow
                                                                                                                                 NonFederatingBackends
                                                                                                                               :> (CanThrow
                                                                                                                                     UnreachableBackends
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             InviteQualified
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'POST
                                                                                                                                                                '[JSON]
                                                                                                                                                                ConvUpdateResponses
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))))))))
                                                                        :<|> (Named
                                                                                "join-conversation-by-id-unqualified"
                                                                                (Summary
                                                                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                                 :> (Until 'V5
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TooManyMembers
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("join"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvJoinResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event))))))))))))))
                                                                              :<|> (Named
                                                                                      "join-conversation-by-code-unqualified"
                                                                                      (Summary
                                                                                         "Join a conversation using a reusable code"
                                                                                       :> (Description
                                                                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (CanThrow
                                                                                                     'CodeNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidConversationPassword
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'GuestLinksDisabled
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'NotATeamMember
                                                                                                                           :> (CanThrow
                                                                                                                                 'TooManyMembers
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> ("join"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     JoinConversationByCode
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvJoinResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "code-check"
                                                                                            (Summary
                                                                                               "Check validity of a conversation code."
                                                                                             :> (Description
                                                                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                                 :> (CanThrow
                                                                                                       'CodeNotFound
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidConversationPassword
                                                                                                             :> ("conversations"
                                                                                                                 :> ("code-check"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationCode
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Valid"]
                                                                                                                              ()))))))))
                                                                                          :<|> (Named
                                                                                                  "create-conversation-code-unqualified@v3"
                                                                                                  (Summary
                                                                                                     "Create or recreate a conversation code"
                                                                                                   :> (Until
                                                                                                         'V4
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'WriteConversationsCode
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'GuestLinksDisabled
                                                                                                                       :> (CanThrow
                                                                                                                             'CreateConversationCodeConflict
                                                                                                                           :> (ZUser
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                                                                :<|> (Named
                                                                                                        "create-conversation-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Create or recreate a conversation code"
                                                                                                         :> (From
                                                                                                               'V4
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'WriteConversationsCode
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'GuestLinksDisabled
                                                                                                                             :> (CanThrow
                                                                                                                                   'CreateConversationCodeConflict
                                                                                                                                 :> (ZUser
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZOptConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               CreateConversationCodeRequest
                                                                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-conversation-guest-links-status"
                                                                                                              (Summary
                                                                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   GuestLinksConfig)))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-code-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Delete conversation code"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("code"
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'DELETE
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[Respond
                                                                                                                                                          200
                                                                                                                                                          "Conversation code deleted."
                                                                                                                                                          Event]
                                                                                                                                                      Event))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-code"
                                                                                                                          (Summary
                                                                                                                             "Get existing conversation code"
                                                                                                                           :> (CanThrow
                                                                                                                                 'CodeNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'GuestLinksDisabled
                                                                                                                                           :> (ZHostOpt
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("code"
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'GET
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[Respond
                                                                                                                                                                        200
                                                                                                                                                                        "Conversation Code"
                                                                                                                                                                        ConversationCodeInfo]
                                                                                                                                                                    ConversationCodeInfo))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "member-typing-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Sending typing notifications"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "update-typing-indicator"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-typing-indicator-updated"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("typing"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           TypingStatus
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'POST
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Notification sent"]
                                                                                                                                                                              ())))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "member-typing-qualified"
                                                                                                                                      (Summary
                                                                                                                                         "Sending typing notifications"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "update-typing-indicator"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-typing-indicator-updated"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("typing"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             TypingStatus
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'POST
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "Notification sent"]
                                                                                                                                                                                ()))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-member-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "leave-conversation"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V2
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                       UserId
                                                                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "remove-member"
                                                                                                                                                  (Summary
                                                                                                                                                     "Remove a member from a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "leave-conversation"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-other-member-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                                           UserId
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-other-member"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update membership of the specified user"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                                                             "usr"
                                                                                                                                                                                                                             UserId
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                                                    ())))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-name"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update conversation name"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                                                       :> (From
                                                                                                                                                                                                                                             'V3
                                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                                                                        'V5
                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"leave-subconversation" (((HasAnnotation 'Remote "galley" "on-mls-message-sent",
  (HasAnnotation 'Remote "galley" "leave-sub-conversation",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ClientId
 -> Qualified ConvId
 -> SubConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvAccessDenied ()), Error MLSProtocolError,
        Error (Tagged 'MLSStaleMessage ()),
        Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "galley" "leave-sub-conversation")
-> QualifiedWithTag 'QLocal UserId
-> ClientId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), Error MLSProtocolError,
       Error (Tagged 'MLSStaleMessage ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-mls-message-sent",
 (HasAnnotation 'Remote "galley" "leave-sub-conversation",
  () :: Constraint)) =>
QualifiedWithTag 'QLocal UserId
-> ClientId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), Error MLSProtocolError,
       Error (Tagged 'MLSStaleMessage ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
QualifiedWithTag 'QLocal UserId
-> ClientId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvAccessDenied ()), Error MLSProtocolError,
       Error (Tagged 'MLSStaleMessage ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(HasLeaveSubConversationEffects r,
 Member (Error MLSProtocolError) r,
 Member (Error FederationError) r,
 Member (Error (Tagged 'MLSStaleMessage ())) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r, Member Resource r,
 Members LeaveSubConversationStaticErrors r) =>
QualifiedWithTag 'QLocal UserId
-> ClientId -> Qualified ConvId -> SubConvId -> Sem r ()
leaveSubConversation)
    API
  (Named
     "leave-subconversation"
     (Summary "Leave an MLS subconversation"
      :> (From 'V5
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'ConvAccessDenied
                          :> (CanThrow 'MLSProtocolErrorTag
                              :> (CanThrow 'MLSStaleMessage
                                  :> (CanThrow 'MLSNotEnabled
                                      :> (ZLocalUser
                                          :> (ZClient
                                              :> ("conversations"
                                                  :> (QualifiedCapture "cnv" ConvId
                                                      :> ("subconversations"
                                                          :> (Capture "subconv" SubConvId
                                                              :> ("self"
                                                                  :> MultiVerb
                                                                       'DELETE
                                                                       '[JSON]
                                                                       '[RespondEmpty 200 "OK"]
                                                                       ())))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "delete-subconversation"
        (Summary "Delete an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'MLSNotEnabled
                             :> (CanThrow 'MLSStaleMessage
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> (QualifiedCapture "cnv" ConvId
                                             :> ("subconversations"
                                                 :> (Capture "subconv" SubConvId
                                                     :> (ReqBody
                                                           '[JSON] DeleteSubConversationRequest
                                                         :> MultiVerb
                                                              'DELETE
                                                              '[JSON]
                                                              '[Respond
                                                                  200 "Deletion successful" ()]
                                                              ())))))))))))))
      :<|> (Named
              "get-subconversation-group-info"
              (Summary "Get MLS group information of subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "query-group-info"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'MLSMissingGroupInfo
                               :> (CanThrow 'MLSNotEnabled
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("subconversations"
                                                   :> (Capture "subconv" SubConvId
                                                       :> ("groupinfo"
                                                           :> MultiVerb
                                                                'GET
                                                                '[MLS]
                                                                '[Respond
                                                                    200
                                                                    "The group information"
                                                                    GroupInfoData]
                                                                GroupInfoData))))))))))))
            :<|> (Named
                    "create-one-to-one-conversation@v2"
                    (Summary "Create a 1:1 conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                             :> (Until 'V3
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NoBindingTeamMembers
                                             :> (CanThrow 'NonBindingTeam
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           UnreachableBackendsLegacy
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> ("one2one"
                                                                                         :> (VersionedReqBody
                                                                                               'V2
                                                                                               '[JSON]
                                                                                               NewConv
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         200
                                                                                                         "Conversation existed"
                                                                                                         Conversation),
                                                                                                    WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         201
                                                                                                         "Conversation created"
                                                                                                         Conversation)]
                                                                                                  (ResponseForExistedCreated
                                                                                                     Conversation))))))))))))))))))))
                  :<|> (Named
                          "create-one-to-one-conversation"
                          (Summary "Create a 1:1 conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-created"
                               :> (From 'V3
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'NoBindingTeamMembers
                                               :> (CanThrow 'NonBindingTeam
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow
                                                                         'MissingLegalholdConsent
                                                                       :> (CanThrow
                                                                             UnreachableBackendsLegacy
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> ("one2one"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewConv
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V3
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V3
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           Conversation)]
                                                                                                    (ResponseForExistedCreated
                                                                                                       Conversation)))))))))))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation@v5"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V5
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                                         :> ("conversations"
                                                             :> ("one2one"
                                                                 :> (QualifiedCapture "usr" UserId
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[VersionedRespond
                                                                              'V5
                                                                              200
                                                                              "MLS 1-1 conversation"
                                                                              Conversation]
                                                                          Conversation))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation@v6"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V6
                                           :> (Until 'V7
                                               :> (ZLocalUser
                                                   :> (CanThrow 'MLSNotEnabled
                                                       :> (CanThrow 'NotConnected
                                                           :> ("conversations"
                                                               :> ("one2one"
                                                                   :> (QualifiedCapture "usr" UserId
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "MLS 1-1 conversation"
                                                                                (MLSOne2OneConversation
                                                                                   MLSPublicKey)]
                                                                            (MLSOne2OneConversation
                                                                               MLSPublicKey))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V7
                                                 :> (ZLocalUser
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> ("conversations"
                                                                 :> ("one2one"
                                                                     :> (QualifiedCapture
                                                                           "usr" UserId
                                                                         :> (QueryParam
                                                                               "format"
                                                                               MLSPublicKeyFormat
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "MLS 1-1 conversation"
                                                                                      (MLSOne2OneConversation
                                                                                         SomeKey)]
                                                                                  (MLSOne2OneConversation
                                                                                     SomeKey))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation-unqualified"
                                                  (Summary
                                                     "Add members to an existing conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (Until 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     Invite
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        ConvUpdateResponses
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation-unqualified2"
                                                        (Summary
                                                           "Add qualified members to an existing conversation."
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (Until 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> ("v2"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               InviteQualified
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation"
                                                              (Summary
                                                                 "Add qualified members to an existing conversation."
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (From 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 InviteQualified
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "join-conversation-by-id-unqualified"
                                                                    (Summary
                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                     :> (Until 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TooManyMembers
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("join"
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvJoinResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event))))))))))))))
                                                                  :<|> (Named
                                                                          "join-conversation-by-code-unqualified"
                                                                          (Summary
                                                                             "Join a conversation using a reusable code"
                                                                           :> (Description
                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (CanThrow
                                                                                         'CodeNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidConversationPassword
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'GuestLinksDisabled
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TooManyMembers
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("join"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         JoinConversationByCode
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvJoinResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))
                                                                        :<|> (Named
                                                                                "code-check"
                                                                                (Summary
                                                                                   "Check validity of a conversation code."
                                                                                 :> (Description
                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                     :> (CanThrow
                                                                                           'CodeNotFound
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidConversationPassword
                                                                                                 :> ("conversations"
                                                                                                     :> ("code-check"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationCode
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Valid"]
                                                                                                                  ()))))))))
                                                                              :<|> (Named
                                                                                      "create-conversation-code-unqualified@v3"
                                                                                      (Summary
                                                                                         "Create or recreate a conversation code"
                                                                                       :> (Until 'V4
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'WriteConversationsCode
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'CreateConversationCodeConflict
                                                                                                               :> (ZUser
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-conversation-code-unqualified"
                                                                                            (Summary
                                                                                               "Create or recreate a conversation code"
                                                                                             :> (From
                                                                                                   'V4
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'WriteConversationsCode
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'CreateConversationCodeConflict
                                                                                                                     :> (ZUser
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-conversation-guest-links-status"
                                                                                                  (Summary
                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("features"
                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Delete conversation code"
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("code"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'DELETE
                                                                                                                                          '[JSON]
                                                                                                                                          '[Respond
                                                                                                                                              200
                                                                                                                                              "Conversation code deleted."
                                                                                                                                              Event]
                                                                                                                                          Event))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-code"
                                                                                                              (Summary
                                                                                                                 "Get existing conversation code"
                                                                                                               :> (CanThrow
                                                                                                                     'CodeNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'GuestLinksDisabled
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[Respond
                                                                                                                                                            200
                                                                                                                                                            "Conversation Code"
                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "member-typing-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Sending typing notifications"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "update-typing-indicator"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("typing"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               TypingStatus
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                  ())))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "member-typing-qualified"
                                                                                                                          (Summary
                                                                                                                             "Sending typing notifications"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "update-typing-indicator"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("typing"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 TypingStatus
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                    ()))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-member-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "leave-conversation"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (Until
                                                                                                                                                       'V2
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                           "usr"
                                                                                                                                                                                           UserId
                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-member"
                                                                                                                                      (Summary
                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "leave-conversation"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-other-member"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                   :> (Description
                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "leave-subconversation"
        (Summary "Leave an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Galley "leave-sub-conversation"
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'MLSProtocolErrorTag
                                 :> (CanThrow 'MLSStaleMessage
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> (ZClient
                                                 :> ("conversations"
                                                     :> (QualifiedCapture "cnv" ConvId
                                                         :> ("subconversations"
                                                             :> (Capture "subconv" SubConvId
                                                                 :> ("self"
                                                                     :> MultiVerb
                                                                          'DELETE
                                                                          '[JSON]
                                                                          '[RespondEmpty 200 "OK"]
                                                                          ()))))))))))))))))
      :<|> (Named
              "delete-subconversation"
              (Summary "Delete an MLS subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'MLSNotEnabled
                                   :> (CanThrow 'MLSStaleMessage
                                       :> (ZLocalUser
                                           :> ("conversations"
                                               :> (QualifiedCapture "cnv" ConvId
                                                   :> ("subconversations"
                                                       :> (Capture "subconv" SubConvId
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 DeleteSubConversationRequest
                                                               :> MultiVerb
                                                                    'DELETE
                                                                    '[JSON]
                                                                    '[Respond
                                                                        200
                                                                        "Deletion successful"
                                                                        ()]
                                                                    ())))))))))))))
            :<|> (Named
                    "get-subconversation-group-info"
                    (Summary "Get MLS group information of subconversation"
                     :> (From 'V5
                         :> (MakesFederatedCall 'Galley "query-group-info"
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'MLSMissingGroupInfo
                                     :> (CanThrow 'MLSNotEnabled
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (QualifiedCapture "cnv" ConvId
                                                     :> ("subconversations"
                                                         :> (Capture "subconv" SubConvId
                                                             :> ("groupinfo"
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[MLS]
                                                                      '[Respond
                                                                          200
                                                                          "The group information"
                                                                          GroupInfoData]
                                                                      GroupInfoData))))))))))))
                  :<|> (Named
                          "create-one-to-one-conversation@v2"
                          (Summary "Create a 1:1 conversation"
                           :> (MakesFederatedCall 'Brig "api-version"
                               :> (MakesFederatedCall 'Galley "on-conversation-created"
                                   :> (Until 'V3
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NoBindingTeamMembers
                                                   :> (CanThrow 'NonBindingTeam
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'NotConnected
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 UnreachableBackendsLegacy
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> ("one2one"
                                                                                               :> (VersionedReqBody
                                                                                                     'V2
                                                                                                     '[JSON]
                                                                                                     NewConv
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               200
                                                                                                               "Conversation existed"
                                                                                                               Conversation),
                                                                                                          WithHeaders
                                                                                                            ConversationHeaders
                                                                                                            Conversation
                                                                                                            (VersionedRespond
                                                                                                               'V2
                                                                                                               201
                                                                                                               "Conversation created"
                                                                                                               Conversation)]
                                                                                                        (ResponseForExistedCreated
                                                                                                           Conversation))))))))))))))))))))
                        :<|> (Named
                                "create-one-to-one-conversation"
                                (Summary "Create a 1:1 conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-created"
                                     :> (From 'V3
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'NoBindingTeamMembers
                                                     :> (CanThrow 'NonBindingTeam
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (CanThrow
                                                                               'MissingLegalholdConsent
                                                                             :> (CanThrow
                                                                                   UnreachableBackendsLegacy
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> ("one2one"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       NewConv
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          '[WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V3
                                                                                                                 200
                                                                                                                 "Conversation existed"
                                                                                                                 Conversation),
                                                                                                            WithHeaders
                                                                                                              ConversationHeaders
                                                                                                              Conversation
                                                                                                              (VersionedRespond
                                                                                                                 'V3
                                                                                                                 201
                                                                                                                 "Conversation created"
                                                                                                                 Conversation)]
                                                                                                          (ResponseForExistedCreated
                                                                                                             Conversation)))))))))))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation@v5"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V5
                                           :> (Until 'V6
                                               :> (ZLocalUser
                                                   :> (CanThrow 'MLSNotEnabled
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow
                                                                 'MLSFederatedOne2OneNotSupported
                                                               :> ("conversations"
                                                                   :> ("one2one"
                                                                       :> (QualifiedCapture
                                                                             "usr" UserId
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[VersionedRespond
                                                                                    'V5
                                                                                    200
                                                                                    "MLS 1-1 conversation"
                                                                                    Conversation]
                                                                                Conversation))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation@v6"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V6
                                                 :> (Until 'V7
                                                     :> (ZLocalUser
                                                         :> (CanThrow 'MLSNotEnabled
                                                             :> (CanThrow 'NotConnected
                                                                 :> ("conversations"
                                                                     :> ("one2one"
                                                                         :> (QualifiedCapture
                                                                               "usr" UserId
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "MLS 1-1 conversation"
                                                                                      (MLSOne2OneConversation
                                                                                         MLSPublicKey)]
                                                                                  (MLSOne2OneConversation
                                                                                     MLSPublicKey))))))))))
                                          :<|> (Named
                                                  "get-one-to-one-mls-conversation"
                                                  (Summary "Get an MLS 1:1 conversation"
                                                   :> (From 'V7
                                                       :> (ZLocalUser
                                                           :> (CanThrow 'MLSNotEnabled
                                                               :> (CanThrow 'NotConnected
                                                                   :> ("conversations"
                                                                       :> ("one2one"
                                                                           :> (QualifiedCapture
                                                                                 "usr" UserId
                                                                               :> (QueryParam
                                                                                     "format"
                                                                                     MLSPublicKeyFormat
                                                                                   :> MultiVerb
                                                                                        'GET
                                                                                        '[JSON]
                                                                                        '[Respond
                                                                                            200
                                                                                            "MLS 1-1 conversation"
                                                                                            (MLSOne2OneConversation
                                                                                               SomeKey)]
                                                                                        (MLSOne2OneConversation
                                                                                           SomeKey))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation-unqualified"
                                                        (Summary
                                                           "Add members to an existing conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (Until 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           Invite
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              ConvUpdateResponses
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation-unqualified2"
                                                              (Summary
                                                                 "Add qualified members to an existing conversation."
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (Until 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> ("v2"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     InviteQualified
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        ConvUpdateResponses
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "add-members-to-conversation"
                                                                    (Summary
                                                                       "Add qualified members to an existing conversation."
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (From 'V2
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'AddConversationMember)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'LeaveConversation)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> (CanThrow
                                                                                                       'TooManyMembers
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'NotConnected
                                                                                                                 :> (CanThrow
                                                                                                                       'MissingLegalholdConsent
                                                                                                                     :> (CanThrow
                                                                                                                           NonFederatingBackends
                                                                                                                         :> (CanThrow
                                                                                                                               UnreachableBackends
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       InviteQualified
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'POST
                                                                                                                                                          '[JSON]
                                                                                                                                                          ConvUpdateResponses
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))))))))
                                                                  :<|> (Named
                                                                          "join-conversation-by-id-unqualified"
                                                                          (Summary
                                                                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                           :> (Until 'V5
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TooManyMembers
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("join"
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvJoinResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event))))))))))))))
                                                                        :<|> (Named
                                                                                "join-conversation-by-code-unqualified"
                                                                                (Summary
                                                                                   "Join a conversation using a reusable code"
                                                                                 :> (Description
                                                                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (CanThrow
                                                                                               'CodeNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidConversationPassword
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'GuestLinksDisabled
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'NotATeamMember
                                                                                                                     :> (CanThrow
                                                                                                                           'TooManyMembers
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> ("join"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               JoinConversationByCode
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvJoinResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))
                                                                              :<|> (Named
                                                                                      "code-check"
                                                                                      (Summary
                                                                                         "Check validity of a conversation code."
                                                                                       :> (Description
                                                                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                           :> (CanThrow
                                                                                                 'CodeNotFound
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidConversationPassword
                                                                                                       :> ("conversations"
                                                                                                           :> ("code-check"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationCode
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Valid"]
                                                                                                                        ()))))))))
                                                                                    :<|> (Named
                                                                                            "create-conversation-code-unqualified@v3"
                                                                                            (Summary
                                                                                               "Create or recreate a conversation code"
                                                                                             :> (Until
                                                                                                   'V4
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'WriteConversationsCode
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'CreateConversationCodeConflict
                                                                                                                     :> (ZUser
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                                                                          :<|> (Named
                                                                                                  "create-conversation-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Create or recreate a conversation code"
                                                                                                   :> (From
                                                                                                         'V4
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'WriteConversationsCode
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'GuestLinksDisabled
                                                                                                                       :> (CanThrow
                                                                                                                             'CreateConversationCodeConflict
                                                                                                                           :> (ZUser
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZOptConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         CreateConversationCodeRequest
                                                                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-conversation-guest-links-status"
                                                                                                        (Summary
                                                                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             GuestLinksConfig)))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-code-unqualified"
                                                                                                              (Summary
                                                                                                                 "Delete conversation code"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("code"
                                                                                                                                           :> MultiVerb
                                                                                                                                                'DELETE
                                                                                                                                                '[JSON]
                                                                                                                                                '[Respond
                                                                                                                                                    200
                                                                                                                                                    "Conversation code deleted."
                                                                                                                                                    Event]
                                                                                                                                                Event))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-code"
                                                                                                                    (Summary
                                                                                                                       "Get existing conversation code"
                                                                                                                     :> (CanThrow
                                                                                                                           'CodeNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'GuestLinksDisabled
                                                                                                                                     :> (ZHostOpt
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("code"
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'GET
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[Respond
                                                                                                                                                                  200
                                                                                                                                                                  "Conversation Code"
                                                                                                                                                                  ConversationCodeInfo]
                                                                                                                                                              ConversationCodeInfo))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "member-typing-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Sending typing notifications"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "update-typing-indicator"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-typing-indicator-updated"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("typing"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     TypingStatus
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'POST
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Notification sent"]
                                                                                                                                                                        ())))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "member-typing-qualified"
                                                                                                                                (Summary
                                                                                                                                   "Sending typing notifications"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "update-typing-indicator"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-typing-indicator-updated"
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("typing"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       TypingStatus
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'POST
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "Notification sent"]
                                                                                                                                                                          ()))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-member-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "leave-conversation"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (Until
                                                                                                                                                             'V2
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                 UserId
                                                                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "remove-member"
                                                                                                                                            (Summary
                                                                                                                                               "Remove a member from a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "leave-conversation"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-other-member-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                                     UserId
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                                            ()))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-other-member"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update membership of the specified user"
                                                                                                                                                         :> (Description
                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("members"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                                                       "usr"
                                                                                                                                                                                                                       UserId
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                                                              ())))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name-deprecated"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-name"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update conversation name"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                                                 :> (From
                                                                                                                                                                                                                                       'V3
                                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                                                                            :> (From
                                                                                                                                                                                                                                                  'V5
                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"delete-subconversation" (((HasAnnotation 'Remote "galley" "delete-sub-conversation",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> SubConvId
 -> DeleteSubConversationRequest
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()), Error (Tagged 'MLSNotEnabled ()),
        Error (Tagged 'MLSStaleMessage ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "delete-sub-conversation")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> DeleteSubConversationRequest
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()), Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'MLSStaleMessage ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "delete-sub-conversation",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> DeleteSubConversationRequest
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()), Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'MLSStaleMessage ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> DeleteSubConversationRequest
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()), Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'MLSStaleMessage ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
Members
  '[ConversationStore, Error (Tagged 'ConvAccessDenied ()),
    Error (Tagged 'ConvNotFound ()), Error (Tagged 'MLSNotEnabled ()),
    Error (Tagged 'MLSStaleMessage ()), Error FederationError,
    FederatorAccess, Input Env, MemberStore, Resource,
    SubConversationStore]
  r =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> DeleteSubConversationRequest
-> Sem r ()
deleteSubConversation)
    API
  (Named
     "delete-subconversation"
     (Summary "Delete an MLS subconversation"
      :> (From 'V5
          :> (MakesFederatedCall 'Galley "delete-sub-conversation"
              :> (CanThrow 'ConvAccessDenied
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'MLSNotEnabled
                          :> (CanThrow 'MLSStaleMessage
                              :> (ZLocalUser
                                  :> ("conversations"
                                      :> (QualifiedCapture "cnv" ConvId
                                          :> ("subconversations"
                                              :> (Capture "subconv" SubConvId
                                                  :> (ReqBody '[JSON] DeleteSubConversationRequest
                                                      :> MultiVerb
                                                           'DELETE
                                                           '[JSON]
                                                           '[Respond 200 "Deletion successful" ()]
                                                           ()))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-subconversation-group-info"
        (Summary "Get MLS group information of subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "query-group-info"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'MLSMissingGroupInfo
                         :> (CanThrow 'MLSNotEnabled
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("subconversations"
                                             :> (Capture "subconv" SubConvId
                                                 :> ("groupinfo"
                                                     :> MultiVerb
                                                          'GET
                                                          '[MLS]
                                                          '[Respond
                                                              200
                                                              "The group information"
                                                              GroupInfoData]
                                                          GroupInfoData))))))))))))
      :<|> (Named
              "create-one-to-one-conversation@v2"
              (Summary "Create a 1:1 conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                       :> (Until 'V3
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NoBindingTeamMembers
                                       :> (CanThrow 'NonBindingTeam
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow
                                                                     UnreachableBackendsLegacy
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> ("one2one"
                                                                                   :> (VersionedReqBody
                                                                                         'V2
                                                                                         '[JSON]
                                                                                         NewConv
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   200
                                                                                                   "Conversation existed"
                                                                                                   Conversation),
                                                                                              WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   201
                                                                                                   "Conversation created"
                                                                                                   Conversation)]
                                                                                            (ResponseForExistedCreated
                                                                                               Conversation))))))))))))))))))))
            :<|> (Named
                    "create-one-to-one-conversation"
                    (Summary "Create a 1:1 conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-created"
                         :> (From 'V3
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'NoBindingTeamMembers
                                         :> (CanThrow 'NonBindingTeam
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow 'MissingLegalholdConsent
                                                                 :> (CanThrow
                                                                       UnreachableBackendsLegacy
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> ("one2one"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewConv
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V3
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V3
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     Conversation)]
                                                                                              (ResponseForExistedCreated
                                                                                                 Conversation)))))))))))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation@v5"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V5
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> (CanThrow 'MLSNotEnabled
                                           :> (CanThrow 'NotConnected
                                               :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                                   :> ("conversations"
                                                       :> ("one2one"
                                                           :> (QualifiedCapture "usr" UserId
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[VersionedRespond
                                                                        'V5
                                                                        200
                                                                        "MLS 1-1 conversation"
                                                                        Conversation]
                                                                    Conversation))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation@v6"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V6
                                     :> (Until 'V7
                                         :> (ZLocalUser
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> (CanThrow 'NotConnected
                                                     :> ("conversations"
                                                         :> ("one2one"
                                                             :> (QualifiedCapture "usr" UserId
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "MLS 1-1 conversation"
                                                                          (MLSOne2OneConversation
                                                                             MLSPublicKey)]
                                                                      (MLSOne2OneConversation
                                                                         MLSPublicKey))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V7
                                           :> (ZLocalUser
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> ("conversations"
                                                           :> ("one2one"
                                                               :> (QualifiedCapture "usr" UserId
                                                                   :> (QueryParam
                                                                         "format" MLSPublicKeyFormat
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "MLS 1-1 conversation"
                                                                                (MLSOne2OneConversation
                                                                                   SomeKey)]
                                                                            (MLSOne2OneConversation
                                                                               SomeKey))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation-unqualified"
                                            (Summary
                                               "Add members to an existing conversation (deprecated)"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (Until 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               Invite
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  ConvUpdateResponses
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation-unqualified2"
                                                  (Summary
                                                     "Add qualified members to an existing conversation."
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (Until 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> ("v2"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         InviteQualified
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvUpdateResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation"
                                                        (Summary
                                                           "Add qualified members to an existing conversation."
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (From 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           InviteQualified
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              ConvUpdateResponses
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))))))))
                                                      :<|> (Named
                                                              "join-conversation-by-id-unqualified"
                                                              (Summary
                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                               :> (Until 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TooManyMembers
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("join"
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvJoinResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event))))))))))))))
                                                            :<|> (Named
                                                                    "join-conversation-by-code-unqualified"
                                                                    (Summary
                                                                       "Join a conversation using a reusable code"
                                                                     :> (Description
                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (CanThrow
                                                                                   'CodeNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidConversationPassword
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'GuestLinksDisabled
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TooManyMembers
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("join"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   JoinConversationByCode
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvJoinResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))
                                                                  :<|> (Named
                                                                          "code-check"
                                                                          (Summary
                                                                             "Check validity of a conversation code."
                                                                           :> (Description
                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                               :> (CanThrow
                                                                                     'CodeNotFound
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidConversationPassword
                                                                                           :> ("conversations"
                                                                                               :> ("code-check"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationCode
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Valid"]
                                                                                                            ()))))))))
                                                                        :<|> (Named
                                                                                "create-conversation-code-unqualified@v3"
                                                                                (Summary
                                                                                   "Create or recreate a conversation code"
                                                                                 :> (Until 'V4
                                                                                     :> (DescriptionOAuthScope
                                                                                           'WriteConversationsCode
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'CreateConversationCodeConflict
                                                                                                         :> (ZUser
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                              :<|> (Named
                                                                                      "create-conversation-code-unqualified"
                                                                                      (Summary
                                                                                         "Create or recreate a conversation code"
                                                                                       :> (From 'V4
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'WriteConversationsCode
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'CreateConversationCodeConflict
                                                                                                               :> (ZUser
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-guest-links-status"
                                                                                            (Summary
                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZUser
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("features"
                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 GuestLinksConfig)))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Delete conversation code"
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("code"
                                                                                                                               :> MultiVerb
                                                                                                                                    'DELETE
                                                                                                                                    '[JSON]
                                                                                                                                    '[Respond
                                                                                                                                        200
                                                                                                                                        "Conversation code deleted."
                                                                                                                                        Event]
                                                                                                                                    Event))))))))
                                                                                                :<|> (Named
                                                                                                        "get-code"
                                                                                                        (Summary
                                                                                                           "Get existing conversation code"
                                                                                                         :> (CanThrow
                                                                                                               'CodeNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'GuestLinksDisabled
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[Respond
                                                                                                                                                      200
                                                                                                                                                      "Conversation Code"
                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                      :<|> (Named
                                                                                                              "member-typing-unqualified"
                                                                                                              (Summary
                                                                                                                 "Sending typing notifications"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "update-typing-indicator"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-typing-indicator-updated"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("typing"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         TypingStatus
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Notification sent"]
                                                                                                                                                            ())))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "member-typing-qualified"
                                                                                                                    (Summary
                                                                                                                       "Sending typing notifications"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "update-typing-indicator"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-typing-indicator-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("typing"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           TypingStatus
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "Notification sent"]
                                                                                                                                                              ()))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-member-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "leave-conversation"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (Until
                                                                                                                                                 'V2
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                     "usr"
                                                                                                                                                                                     UserId
                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-member"
                                                                                                                                (Summary
                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "leave-conversation"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("members"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-other-member"
                                                                                                                                            (Summary
                                                                                                                                               "Update membership of the specified user"
                                                                                                                                             :> (Description
                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                           UserId
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "delete-subconversation"
        (Summary "Delete an MLS subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "delete-sub-conversation"
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'MLSNotEnabled
                             :> (CanThrow 'MLSStaleMessage
                                 :> (ZLocalUser
                                     :> ("conversations"
                                         :> (QualifiedCapture "cnv" ConvId
                                             :> ("subconversations"
                                                 :> (Capture "subconv" SubConvId
                                                     :> (ReqBody
                                                           '[JSON] DeleteSubConversationRequest
                                                         :> MultiVerb
                                                              'DELETE
                                                              '[JSON]
                                                              '[Respond
                                                                  200 "Deletion successful" ()]
                                                              ())))))))))))))
      :<|> (Named
              "get-subconversation-group-info"
              (Summary "Get MLS group information of subconversation"
               :> (From 'V5
                   :> (MakesFederatedCall 'Galley "query-group-info"
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'MLSMissingGroupInfo
                               :> (CanThrow 'MLSNotEnabled
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (QualifiedCapture "cnv" ConvId
                                               :> ("subconversations"
                                                   :> (Capture "subconv" SubConvId
                                                       :> ("groupinfo"
                                                           :> MultiVerb
                                                                'GET
                                                                '[MLS]
                                                                '[Respond
                                                                    200
                                                                    "The group information"
                                                                    GroupInfoData]
                                                                GroupInfoData))))))))))))
            :<|> (Named
                    "create-one-to-one-conversation@v2"
                    (Summary "Create a 1:1 conversation"
                     :> (MakesFederatedCall 'Brig "api-version"
                         :> (MakesFederatedCall 'Galley "on-conversation-created"
                             :> (Until 'V3
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NoBindingTeamMembers
                                             :> (CanThrow 'NonBindingTeam
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'NotConnected
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           UnreachableBackendsLegacy
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> ("one2one"
                                                                                         :> (VersionedReqBody
                                                                                               'V2
                                                                                               '[JSON]
                                                                                               NewConv
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         200
                                                                                                         "Conversation existed"
                                                                                                         Conversation),
                                                                                                    WithHeaders
                                                                                                      ConversationHeaders
                                                                                                      Conversation
                                                                                                      (VersionedRespond
                                                                                                         'V2
                                                                                                         201
                                                                                                         "Conversation created"
                                                                                                         Conversation)]
                                                                                                  (ResponseForExistedCreated
                                                                                                     Conversation))))))))))))))))))))
                  :<|> (Named
                          "create-one-to-one-conversation"
                          (Summary "Create a 1:1 conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-created"
                               :> (From 'V3
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'NoBindingTeamMembers
                                               :> (CanThrow 'NonBindingTeam
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (CanThrow
                                                                         'MissingLegalholdConsent
                                                                       :> (CanThrow
                                                                             UnreachableBackendsLegacy
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> ("one2one"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 NewConv
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    '[WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V3
                                                                                                           200
                                                                                                           "Conversation existed"
                                                                                                           Conversation),
                                                                                                      WithHeaders
                                                                                                        ConversationHeaders
                                                                                                        Conversation
                                                                                                        (VersionedRespond
                                                                                                           'V3
                                                                                                           201
                                                                                                           "Conversation created"
                                                                                                           Conversation)]
                                                                                                    (ResponseForExistedCreated
                                                                                                       Conversation)))))))))))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation@v5"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V5
                                     :> (Until 'V6
                                         :> (ZLocalUser
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                                         :> ("conversations"
                                                             :> ("one2one"
                                                                 :> (QualifiedCapture "usr" UserId
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[VersionedRespond
                                                                              'V5
                                                                              200
                                                                              "MLS 1-1 conversation"
                                                                              Conversation]
                                                                          Conversation))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation@v6"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V6
                                           :> (Until 'V7
                                               :> (ZLocalUser
                                                   :> (CanThrow 'MLSNotEnabled
                                                       :> (CanThrow 'NotConnected
                                                           :> ("conversations"
                                                               :> ("one2one"
                                                                   :> (QualifiedCapture "usr" UserId
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "MLS 1-1 conversation"
                                                                                (MLSOne2OneConversation
                                                                                   MLSPublicKey)]
                                                                            (MLSOne2OneConversation
                                                                               MLSPublicKey))))))))))
                                    :<|> (Named
                                            "get-one-to-one-mls-conversation"
                                            (Summary "Get an MLS 1:1 conversation"
                                             :> (From 'V7
                                                 :> (ZLocalUser
                                                     :> (CanThrow 'MLSNotEnabled
                                                         :> (CanThrow 'NotConnected
                                                             :> ("conversations"
                                                                 :> ("one2one"
                                                                     :> (QualifiedCapture
                                                                           "usr" UserId
                                                                         :> (QueryParam
                                                                               "format"
                                                                               MLSPublicKeyFormat
                                                                             :> MultiVerb
                                                                                  'GET
                                                                                  '[JSON]
                                                                                  '[Respond
                                                                                      200
                                                                                      "MLS 1-1 conversation"
                                                                                      (MLSOne2OneConversation
                                                                                         SomeKey)]
                                                                                  (MLSOne2OneConversation
                                                                                     SomeKey))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation-unqualified"
                                                  (Summary
                                                     "Add members to an existing conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (Until 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     Invite
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        ConvUpdateResponses
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation-unqualified2"
                                                        (Summary
                                                           "Add qualified members to an existing conversation."
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (Until 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> ("v2"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               InviteQualified
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  ConvUpdateResponses
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))))))))
                                                      :<|> (Named
                                                              "add-members-to-conversation"
                                                              (Summary
                                                                 "Add qualified members to an existing conversation."
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (From 'V2
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'AddConversationMember)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'LeaveConversation)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> (CanThrow
                                                                                                 'TooManyMembers
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'NotConnected
                                                                                                           :> (CanThrow
                                                                                                                 'MissingLegalholdConsent
                                                                                                               :> (CanThrow
                                                                                                                     NonFederatingBackends
                                                                                                                   :> (CanThrow
                                                                                                                         UnreachableBackends
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 InviteQualified
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'POST
                                                                                                                                                    '[JSON]
                                                                                                                                                    ConvUpdateResponses
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))))))))
                                                            :<|> (Named
                                                                    "join-conversation-by-id-unqualified"
                                                                    (Summary
                                                                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                                     :> (Until 'V5
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TooManyMembers
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("join"
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvJoinResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event))))))))))))))
                                                                  :<|> (Named
                                                                          "join-conversation-by-code-unqualified"
                                                                          (Summary
                                                                             "Join a conversation using a reusable code"
                                                                           :> (Description
                                                                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (CanThrow
                                                                                         'CodeNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidConversationPassword
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'GuestLinksDisabled
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'NotATeamMember
                                                                                                               :> (CanThrow
                                                                                                                     'TooManyMembers
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> ("join"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         JoinConversationByCode
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvJoinResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))
                                                                        :<|> (Named
                                                                                "code-check"
                                                                                (Summary
                                                                                   "Check validity of a conversation code."
                                                                                 :> (Description
                                                                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                                     :> (CanThrow
                                                                                           'CodeNotFound
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidConversationPassword
                                                                                                 :> ("conversations"
                                                                                                     :> ("code-check"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationCode
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Valid"]
                                                                                                                  ()))))))))
                                                                              :<|> (Named
                                                                                      "create-conversation-code-unqualified@v3"
                                                                                      (Summary
                                                                                         "Create or recreate a conversation code"
                                                                                       :> (Until 'V4
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'WriteConversationsCode
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'CreateConversationCodeConflict
                                                                                                               :> (ZUser
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                                                                    :<|> (Named
                                                                                            "create-conversation-code-unqualified"
                                                                                            (Summary
                                                                                               "Create or recreate a conversation code"
                                                                                             :> (From
                                                                                                   'V4
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'WriteConversationsCode
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'GuestLinksDisabled
                                                                                                                 :> (CanThrow
                                                                                                                       'CreateConversationCodeConflict
                                                                                                                     :> (ZUser
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZOptConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   CreateConversationCodeRequest
                                                                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-conversation-guest-links-status"
                                                                                                  (Summary
                                                                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("features"
                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       GuestLinksConfig)))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-code-unqualified"
                                                                                                        (Summary
                                                                                                           "Delete conversation code"
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("code"
                                                                                                                                     :> MultiVerb
                                                                                                                                          'DELETE
                                                                                                                                          '[JSON]
                                                                                                                                          '[Respond
                                                                                                                                              200
                                                                                                                                              "Conversation code deleted."
                                                                                                                                              Event]
                                                                                                                                          Event))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-code"
                                                                                                              (Summary
                                                                                                                 "Get existing conversation code"
                                                                                                               :> (CanThrow
                                                                                                                     'CodeNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'GuestLinksDisabled
                                                                                                                               :> (ZHostOpt
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("code"
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'GET
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[Respond
                                                                                                                                                            200
                                                                                                                                                            "Conversation Code"
                                                                                                                                                            ConversationCodeInfo]
                                                                                                                                                        ConversationCodeInfo))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "member-typing-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Sending typing notifications"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "update-typing-indicator"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-typing-indicator-updated"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("typing"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               TypingStatus
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'POST
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Notification sent"]
                                                                                                                                                                  ())))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "member-typing-qualified"
                                                                                                                          (Summary
                                                                                                                             "Sending typing notifications"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "update-typing-indicator"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-typing-indicator-updated"
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("typing"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 TypingStatus
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'POST
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "Notification sent"]
                                                                                                                                                                    ()))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-member-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "leave-conversation"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (Until
                                                                                                                                                       'V2
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                           "usr"
                                                                                                                                                                                           UserId
                                                                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "remove-member"
                                                                                                                                      (Summary
                                                                                                                                         "Remove a member from a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "leave-conversation"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-other-member-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update membership of the specified user (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                                               "usr"
                                                                                                                                                                                                               UserId
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                                      ()))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-other-member"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update membership of the specified user"
                                                                                                                                                   :> (Description
                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidTarget
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("members"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                                                 "usr"
                                                                                                                                                                                                                 UserId
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                            200
                                                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                                                        ())))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name-deprecated"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("name"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-name"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update conversation name"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-message-timer"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "update-conversation"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Galley
                                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Brig
                                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-access"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                                             'Brig
                                                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                                                           :> (From
                                                                                                                                                                                                                                 'V3
                                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                                                                      :> (From
                                                                                                                                                                                                                                            'V5
                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-subconversation-group-info" (((HasAnnotation 'Remote "galley" "query-group-info",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> Qualified ConvId
 -> SubConvId
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'MLSMissingGroupInfo ()),
        Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      GroupInfoData)
-> Dict (HasAnnotation 'Remote "galley" "query-group-info")
-> QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "query-group-info",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId
-> SubConvId
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'MLSMissingGroupInfo ()),
       Error (Tagged 'MLSNotEnabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     GroupInfoData
forall (r :: EffectRow).
(Members
   '[ConversationStore, Error FederationError, FederatorAccess,
     Input Env, MemberStore, SubConversationStore]
   r,
 Members
   '[Error (Tagged 'ConvNotFound ()),
     Error (Tagged 'MLSMissingGroupInfo ()),
     Error (Tagged 'MLSNotEnabled ())]
   r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified ConvId -> SubConvId -> Sem r GroupInfoData
getSubConversationGroupInfo)
    API
  (Named
     "get-subconversation-group-info"
     (Summary "Get MLS group information of subconversation"
      :> (From 'V5
          :> (MakesFederatedCall 'Galley "query-group-info"
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'MLSMissingGroupInfo
                      :> (CanThrow 'MLSNotEnabled
                          :> (ZLocalUser
                              :> ("conversations"
                                  :> (QualifiedCapture "cnv" ConvId
                                      :> ("subconversations"
                                          :> (Capture "subconv" SubConvId
                                              :> ("groupinfo"
                                                  :> MultiVerb
                                                       'GET
                                                       '[MLS]
                                                       '[Respond
                                                           200
                                                           "The group information"
                                                           GroupInfoData]
                                                       GroupInfoData)))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-one-to-one-conversation@v2"
        (Summary "Create a 1:1 conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Galley "on-conversation-created"
                 :> (Until 'V3
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NoBindingTeamMembers
                                 :> (CanThrow 'NonBindingTeam
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow UnreachableBackendsLegacy
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> ("one2one"
                                                                             :> (VersionedReqBody
                                                                                   'V2
                                                                                   '[JSON]
                                                                                   NewConv
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             200
                                                                                             "Conversation existed"
                                                                                             Conversation),
                                                                                        WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             201
                                                                                             "Conversation created"
                                                                                             Conversation)]
                                                                                      (ResponseForExistedCreated
                                                                                         Conversation))))))))))))))))))))
      :<|> (Named
              "create-one-to-one-conversation"
              (Summary "Create a 1:1 conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-created"
                   :> (From 'V3
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'InvalidOperation
                               :> (CanThrow 'NoBindingTeamMembers
                                   :> (CanThrow 'NonBindingTeam
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'NotConnected
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow 'MissingLegalholdConsent
                                                           :> (CanThrow UnreachableBackendsLegacy
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> ("one2one"
                                                                               :> (ReqBody
                                                                                     '[JSON] NewConv
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V3
                                                                                               200
                                                                                               "Conversation existed"
                                                                                               Conversation),
                                                                                          WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V3
                                                                                               201
                                                                                               "Conversation created"
                                                                                               Conversation)]
                                                                                        (ResponseForExistedCreated
                                                                                           Conversation)))))))))))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation@v5"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V5
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> (CanThrow 'MLSNotEnabled
                                     :> (CanThrow 'NotConnected
                                         :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                             :> ("conversations"
                                                 :> ("one2one"
                                                     :> (QualifiedCapture "usr" UserId
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[VersionedRespond
                                                                  'V5
                                                                  200
                                                                  "MLS 1-1 conversation"
                                                                  Conversation]
                                                              Conversation))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation@v6"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V6
                               :> (Until 'V7
                                   :> (ZLocalUser
                                       :> (CanThrow 'MLSNotEnabled
                                           :> (CanThrow 'NotConnected
                                               :> ("conversations"
                                                   :> ("one2one"
                                                       :> (QualifiedCapture "usr" UserId
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "MLS 1-1 conversation"
                                                                    (MLSOne2OneConversation
                                                                       MLSPublicKey)]
                                                                (MLSOne2OneConversation
                                                                   MLSPublicKey))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V7
                                     :> (ZLocalUser
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> ("conversations"
                                                     :> ("one2one"
                                                         :> (QualifiedCapture "usr" UserId
                                                             :> (QueryParam
                                                                   "format" MLSPublicKeyFormat
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "MLS 1-1 conversation"
                                                                          (MLSOne2OneConversation
                                                                             SomeKey)]
                                                                      (MLSOne2OneConversation
                                                                         SomeKey))))))))))
                              :<|> (Named
                                      "add-members-to-conversation-unqualified"
                                      (Summary
                                         "Add members to an existing conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (Until 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         Invite
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            ConvUpdateResponses
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation-unqualified2"
                                            (Summary
                                               "Add qualified members to an existing conversation."
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (Until 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> ("v2"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   InviteQualified
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvUpdateResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation"
                                                  (Summary
                                                     "Add qualified members to an existing conversation."
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (From 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     InviteQualified
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        ConvUpdateResponses
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))))))))
                                                :<|> (Named
                                                        "join-conversation-by-id-unqualified"
                                                        (Summary
                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                         :> (Until 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TooManyMembers
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("join"
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvJoinResponses
                                                                                                              (UpdateResult
                                                                                                                 Event))))))))))))))
                                                      :<|> (Named
                                                              "join-conversation-by-code-unqualified"
                                                              (Summary
                                                                 "Join a conversation using a reusable code"
                                                               :> (Description
                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (CanThrow 'CodeNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidConversationPassword
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'GuestLinksDisabled
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TooManyMembers
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> ("join"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             JoinConversationByCode
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvJoinResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))
                                                            :<|> (Named
                                                                    "code-check"
                                                                    (Summary
                                                                       "Check validity of a conversation code."
                                                                     :> (Description
                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                         :> (CanThrow 'CodeNotFound
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidConversationPassword
                                                                                     :> ("conversations"
                                                                                         :> ("code-check"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationCode
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Valid"]
                                                                                                      ()))))))))
                                                                  :<|> (Named
                                                                          "create-conversation-code-unqualified@v3"
                                                                          (Summary
                                                                             "Create or recreate a conversation code"
                                                                           :> (Until 'V4
                                                                               :> (DescriptionOAuthScope
                                                                                     'WriteConversationsCode
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'CreateConversationCodeConflict
                                                                                                   :> (ZUser
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                        :<|> (Named
                                                                                "create-conversation-code-unqualified"
                                                                                (Summary
                                                                                   "Create or recreate a conversation code"
                                                                                 :> (From 'V4
                                                                                     :> (DescriptionOAuthScope
                                                                                           'WriteConversationsCode
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'CreateConversationCodeConflict
                                                                                                         :> (ZUser
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-guest-links-status"
                                                                                      (Summary
                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZUser
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("features"
                                                                                                               :> ("conversationGuestLinks"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           GuestLinksConfig)))))))))
                                                                                    :<|> (Named
                                                                                            "remove-code-unqualified"
                                                                                            (Summary
                                                                                               "Delete conversation code"
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("code"
                                                                                                                         :> MultiVerb
                                                                                                                              'DELETE
                                                                                                                              '[JSON]
                                                                                                                              '[Respond
                                                                                                                                  200
                                                                                                                                  "Conversation code deleted."
                                                                                                                                  Event]
                                                                                                                              Event))))))))
                                                                                          :<|> (Named
                                                                                                  "get-code"
                                                                                                  (Summary
                                                                                                     "Get existing conversation code"
                                                                                                   :> (CanThrow
                                                                                                         'CodeNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'GuestLinksDisabled
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[Respond
                                                                                                                                                200
                                                                                                                                                "Conversation Code"
                                                                                                                                                ConversationCodeInfo]
                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                :<|> (Named
                                                                                                        "member-typing-unqualified"
                                                                                                        (Summary
                                                                                                           "Sending typing notifications"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "update-typing-indicator"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-typing-indicator-updated"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("typing"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   TypingStatus
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Notification sent"]
                                                                                                                                                      ())))))))))))
                                                                                                      :<|> (Named
                                                                                                              "member-typing-qualified"
                                                                                                              (Summary
                                                                                                                 "Sending typing notifications"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "update-typing-indicator"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-typing-indicator-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("typing"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     TypingStatus
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "Notification sent"]
                                                                                                                                                        ()))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-member-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "leave-conversation"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (Until
                                                                                                                                           'V2
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                               "usr"
                                                                                                                                                                               UserId
                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-member"
                                                                                                                          (Summary
                                                                                                                             "Remove a member from a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "leave-conversation"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("members"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-other-member-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-other-member"
                                                                                                                                      (Summary
                                                                                                                                         "Update membership of the specified user"
                                                                                                                                       :> (Description
                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                     UserId
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-subconversation-group-info"
        (Summary "Get MLS group information of subconversation"
         :> (From 'V5
             :> (MakesFederatedCall 'Galley "query-group-info"
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'MLSMissingGroupInfo
                         :> (CanThrow 'MLSNotEnabled
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (QualifiedCapture "cnv" ConvId
                                         :> ("subconversations"
                                             :> (Capture "subconv" SubConvId
                                                 :> ("groupinfo"
                                                     :> MultiVerb
                                                          'GET
                                                          '[MLS]
                                                          '[Respond
                                                              200
                                                              "The group information"
                                                              GroupInfoData]
                                                          GroupInfoData))))))))))))
      :<|> (Named
              "create-one-to-one-conversation@v2"
              (Summary "Create a 1:1 conversation"
               :> (MakesFederatedCall 'Brig "api-version"
                   :> (MakesFederatedCall 'Galley "on-conversation-created"
                       :> (Until 'V3
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NoBindingTeamMembers
                                       :> (CanThrow 'NonBindingTeam
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'NotConnected
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow
                                                                     UnreachableBackendsLegacy
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> ("one2one"
                                                                                   :> (VersionedReqBody
                                                                                         'V2
                                                                                         '[JSON]
                                                                                         NewConv
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   200
                                                                                                   "Conversation existed"
                                                                                                   Conversation),
                                                                                              WithHeaders
                                                                                                ConversationHeaders
                                                                                                Conversation
                                                                                                (VersionedRespond
                                                                                                   'V2
                                                                                                   201
                                                                                                   "Conversation created"
                                                                                                   Conversation)]
                                                                                            (ResponseForExistedCreated
                                                                                               Conversation))))))))))))))))))))
            :<|> (Named
                    "create-one-to-one-conversation"
                    (Summary "Create a 1:1 conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-created"
                         :> (From 'V3
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'NoBindingTeamMembers
                                         :> (CanThrow 'NonBindingTeam
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (CanThrow 'MissingLegalholdConsent
                                                                 :> (CanThrow
                                                                       UnreachableBackendsLegacy
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> ("one2one"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           NewConv
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              '[WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V3
                                                                                                     200
                                                                                                     "Conversation existed"
                                                                                                     Conversation),
                                                                                                WithHeaders
                                                                                                  ConversationHeaders
                                                                                                  Conversation
                                                                                                  (VersionedRespond
                                                                                                     'V3
                                                                                                     201
                                                                                                     "Conversation created"
                                                                                                     Conversation)]
                                                                                              (ResponseForExistedCreated
                                                                                                 Conversation)))))))))))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation@v5"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V5
                               :> (Until 'V6
                                   :> (ZLocalUser
                                       :> (CanThrow 'MLSNotEnabled
                                           :> (CanThrow 'NotConnected
                                               :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                                   :> ("conversations"
                                                       :> ("one2one"
                                                           :> (QualifiedCapture "usr" UserId
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[VersionedRespond
                                                                        'V5
                                                                        200
                                                                        "MLS 1-1 conversation"
                                                                        Conversation]
                                                                    Conversation))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation@v6"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V6
                                     :> (Until 'V7
                                         :> (ZLocalUser
                                             :> (CanThrow 'MLSNotEnabled
                                                 :> (CanThrow 'NotConnected
                                                     :> ("conversations"
                                                         :> ("one2one"
                                                             :> (QualifiedCapture "usr" UserId
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "MLS 1-1 conversation"
                                                                          (MLSOne2OneConversation
                                                                             MLSPublicKey)]
                                                                      (MLSOne2OneConversation
                                                                         MLSPublicKey))))))))))
                              :<|> (Named
                                      "get-one-to-one-mls-conversation"
                                      (Summary "Get an MLS 1:1 conversation"
                                       :> (From 'V7
                                           :> (ZLocalUser
                                               :> (CanThrow 'MLSNotEnabled
                                                   :> (CanThrow 'NotConnected
                                                       :> ("conversations"
                                                           :> ("one2one"
                                                               :> (QualifiedCapture "usr" UserId
                                                                   :> (QueryParam
                                                                         "format" MLSPublicKeyFormat
                                                                       :> MultiVerb
                                                                            'GET
                                                                            '[JSON]
                                                                            '[Respond
                                                                                200
                                                                                "MLS 1-1 conversation"
                                                                                (MLSOne2OneConversation
                                                                                   SomeKey)]
                                                                            (MLSOne2OneConversation
                                                                               SomeKey))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation-unqualified"
                                            (Summary
                                               "Add members to an existing conversation (deprecated)"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (Until 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               Invite
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  ConvUpdateResponses
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation-unqualified2"
                                                  (Summary
                                                     "Add qualified members to an existing conversation."
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (Until 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> ("v2"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         InviteQualified
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            ConvUpdateResponses
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))))))))
                                                :<|> (Named
                                                        "add-members-to-conversation"
                                                        (Summary
                                                           "Add qualified members to an existing conversation."
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (From 'V2
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'AddConversationMember)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'LeaveConversation)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> (CanThrow
                                                                                           'TooManyMembers
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'NotConnected
                                                                                                     :> (CanThrow
                                                                                                           'MissingLegalholdConsent
                                                                                                         :> (CanThrow
                                                                                                               NonFederatingBackends
                                                                                                             :> (CanThrow
                                                                                                                   UnreachableBackends
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           InviteQualified
                                                                                                                                         :> MultiVerb
                                                                                                                                              'POST
                                                                                                                                              '[JSON]
                                                                                                                                              ConvUpdateResponses
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))))))))
                                                      :<|> (Named
                                                              "join-conversation-by-id-unqualified"
                                                              (Summary
                                                                 "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                               :> (Until 'V5
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TooManyMembers
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("join"
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvJoinResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event))))))))))))))
                                                            :<|> (Named
                                                                    "join-conversation-by-code-unqualified"
                                                                    (Summary
                                                                       "Join a conversation using a reusable code"
                                                                     :> (Description
                                                                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (CanThrow
                                                                                   'CodeNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidConversationPassword
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'GuestLinksDisabled
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'NotATeamMember
                                                                                                         :> (CanThrow
                                                                                                               'TooManyMembers
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> ("join"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   JoinConversationByCode
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvJoinResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))
                                                                  :<|> (Named
                                                                          "code-check"
                                                                          (Summary
                                                                             "Check validity of a conversation code."
                                                                           :> (Description
                                                                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                               :> (CanThrow
                                                                                     'CodeNotFound
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidConversationPassword
                                                                                           :> ("conversations"
                                                                                               :> ("code-check"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationCode
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Valid"]
                                                                                                            ()))))))))
                                                                        :<|> (Named
                                                                                "create-conversation-code-unqualified@v3"
                                                                                (Summary
                                                                                   "Create or recreate a conversation code"
                                                                                 :> (Until 'V4
                                                                                     :> (DescriptionOAuthScope
                                                                                           'WriteConversationsCode
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'CreateConversationCodeConflict
                                                                                                         :> (ZUser
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> CreateConversationCodeVerb)))))))))))))
                                                                              :<|> (Named
                                                                                      "create-conversation-code-unqualified"
                                                                                      (Summary
                                                                                         "Create or recreate a conversation code"
                                                                                       :> (From 'V4
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'WriteConversationsCode
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'GuestLinksDisabled
                                                                                                           :> (CanThrow
                                                                                                                 'CreateConversationCodeConflict
                                                                                                               :> (ZUser
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZOptConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             CreateConversationCodeRequest
                                                                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-guest-links-status"
                                                                                            (Summary
                                                                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZUser
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("features"
                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 GuestLinksConfig)))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-code-unqualified"
                                                                                                  (Summary
                                                                                                     "Delete conversation code"
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("code"
                                                                                                                               :> MultiVerb
                                                                                                                                    'DELETE
                                                                                                                                    '[JSON]
                                                                                                                                    '[Respond
                                                                                                                                        200
                                                                                                                                        "Conversation code deleted."
                                                                                                                                        Event]
                                                                                                                                    Event))))))))
                                                                                                :<|> (Named
                                                                                                        "get-code"
                                                                                                        (Summary
                                                                                                           "Get existing conversation code"
                                                                                                         :> (CanThrow
                                                                                                               'CodeNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'GuestLinksDisabled
                                                                                                                         :> (ZHostOpt
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("code"
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'GET
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[Respond
                                                                                                                                                      200
                                                                                                                                                      "Conversation Code"
                                                                                                                                                      ConversationCodeInfo]
                                                                                                                                                  ConversationCodeInfo))))))))))
                                                                                                      :<|> (Named
                                                                                                              "member-typing-unqualified"
                                                                                                              (Summary
                                                                                                                 "Sending typing notifications"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "update-typing-indicator"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-typing-indicator-updated"
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("typing"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         TypingStatus
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'POST
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Notification sent"]
                                                                                                                                                            ())))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "member-typing-qualified"
                                                                                                                    (Summary
                                                                                                                       "Sending typing notifications"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "update-typing-indicator"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-typing-indicator-updated"
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("typing"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           TypingStatus
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'POST
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "Notification sent"]
                                                                                                                                                              ()))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-member-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Remove a member from a conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "leave-conversation"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (Until
                                                                                                                                                 'V2
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("members"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                     "usr"
                                                                                                                                                                                     UserId
                                                                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "remove-member"
                                                                                                                                (Summary
                                                                                                                                   "Remove a member from a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "leave-conversation"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("members"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-other-member-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update membership of the specified user (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("members"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                                         "usr"
                                                                                                                                                                                                         UserId
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                                ()))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-other-member"
                                                                                                                                            (Summary
                                                                                                                                               "Update membership of the specified user"
                                                                                                                                             :> (Description
                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvMemberNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidTarget
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("members"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                                                           "usr"
                                                                                                                                                                                                           UserId
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                      200
                                                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                                                  ())))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name-deprecated"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("name"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-name"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update conversation name"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Brig
                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-message-timer"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update the message timer for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "update-conversation"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Galley
                                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Brig
                                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-access"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                                               'Galley
                                                                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                                       'Brig
                                                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                                                     :> (From
                                                                                                                                                                                                                           'V3
                                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (Maybe
                                                                                                                                                                                                                                           Member)))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                                                                :> (From
                                                                                                                                                                                                                                      'V5
                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-one-to-one-conversation@v2" (((HasAnnotation 'Remote "brig" "api-version",
  (HasAnnotation 'Remote "galley" "on-conversation-created",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NoBindingTeamMembers ()),
        Error (Tagged 'NonBindingTeam ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
        Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> Dict (HasAnnotation 'Remote "brig" "api-version")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "brig" "api-version",
 (HasAnnotation 'Remote "galley" "on-conversation-created",
  () :: Constraint)) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r, Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member (Error (Tagged 'NoBindingTeamMembers ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error UnreachableBackendsLegacy) r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> NewConv -> Sem r (ConversationResponse Conversation)
createOne2OneConversation)
    API
  (Named
     "create-one-to-one-conversation@v2"
     (Summary "Create a 1:1 conversation"
      :> (MakesFederatedCall 'Brig "api-version"
          :> (MakesFederatedCall 'Galley "on-conversation-created"
              :> (Until 'V3
                  :> (CanThrow 'ConvAccessDenied
                      :> (CanThrow 'InvalidOperation
                          :> (CanThrow 'NoBindingTeamMembers
                              :> (CanThrow 'NonBindingTeam
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'NotConnected
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'TeamNotFound
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow UnreachableBackendsLegacy
                                                          :> (ZLocalUser
                                                              :> (ZConn
                                                                  :> ("conversations"
                                                                      :> ("one2one"
                                                                          :> (VersionedReqBody
                                                                                'V2 '[JSON] NewConv
                                                                              :> MultiVerb
                                                                                   'POST
                                                                                   '[JSON]
                                                                                   '[WithHeaders
                                                                                       ConversationHeaders
                                                                                       Conversation
                                                                                       (VersionedRespond
                                                                                          'V2
                                                                                          200
                                                                                          "Conversation existed"
                                                                                          Conversation),
                                                                                     WithHeaders
                                                                                       ConversationHeaders
                                                                                       Conversation
                                                                                       (VersionedRespond
                                                                                          'V2
                                                                                          201
                                                                                          "Conversation created"
                                                                                          Conversation)]
                                                                                   (ResponseForExistedCreated
                                                                                      Conversation)))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-one-to-one-conversation"
        (Summary "Create a 1:1 conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-created"
             :> (From 'V3
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'InvalidOperation
                         :> (CanThrow 'NoBindingTeamMembers
                             :> (CanThrow 'NonBindingTeam
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'NotConnected
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow 'MissingLegalholdConsent
                                                     :> (CanThrow UnreachableBackendsLegacy
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> ("one2one"
                                                                         :> (ReqBody '[JSON] NewConv
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V3
                                                                                         200
                                                                                         "Conversation existed"
                                                                                         Conversation),
                                                                                    WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V3
                                                                                         201
                                                                                         "Conversation created"
                                                                                         Conversation)]
                                                                                  (ResponseForExistedCreated
                                                                                     Conversation)))))))))))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation@v5"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V5
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> (CanThrow 'MLSNotEnabled
                               :> (CanThrow 'NotConnected
                                   :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                       :> ("conversations"
                                           :> ("one2one"
                                               :> (QualifiedCapture "usr" UserId
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[VersionedRespond
                                                            'V5
                                                            200
                                                            "MLS 1-1 conversation"
                                                            Conversation]
                                                        Conversation))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation@v6"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V6
                         :> (Until 'V7
                             :> (ZLocalUser
                                 :> (CanThrow 'MLSNotEnabled
                                     :> (CanThrow 'NotConnected
                                         :> ("conversations"
                                             :> ("one2one"
                                                 :> (QualifiedCapture "usr" UserId
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "MLS 1-1 conversation"
                                                              (MLSOne2OneConversation MLSPublicKey)]
                                                          (MLSOne2OneConversation
                                                             MLSPublicKey))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V7
                               :> (ZLocalUser
                                   :> (CanThrow 'MLSNotEnabled
                                       :> (CanThrow 'NotConnected
                                           :> ("conversations"
                                               :> ("one2one"
                                                   :> (QualifiedCapture "usr" UserId
                                                       :> (QueryParam "format" MLSPublicKeyFormat
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "MLS 1-1 conversation"
                                                                    (MLSOne2OneConversation
                                                                       SomeKey)]
                                                                (MLSOne2OneConversation
                                                                   SomeKey))))))))))
                        :<|> (Named
                                "add-members-to-conversation-unqualified"
                                (Summary "Add members to an existing conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (Until 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   Invite
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      ConvUpdateResponses
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))))))))
                              :<|> (Named
                                      "add-members-to-conversation-unqualified2"
                                      (Summary "Add qualified members to an existing conversation."
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (Until 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> ("v2"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             InviteQualified
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvUpdateResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation"
                                            (Summary
                                               "Add qualified members to an existing conversation."
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (From 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               InviteQualified
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  ConvUpdateResponses
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))))))))
                                          :<|> (Named
                                                  "join-conversation-by-id-unqualified"
                                                  (Summary
                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                   :> (Until 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TooManyMembers
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("join"
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvJoinResponses
                                                                                                        (UpdateResult
                                                                                                           Event))))))))))))))
                                                :<|> (Named
                                                        "join-conversation-by-code-unqualified"
                                                        (Summary
                                                           "Join a conversation using a reusable code"
                                                         :> (Description
                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (CanThrow 'CodeNotFound
                                                                     :> (CanThrow
                                                                           'InvalidConversationPassword
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'GuestLinksDisabled
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TooManyMembers
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> ("join"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       JoinConversationByCode
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvJoinResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))
                                                      :<|> (Named
                                                              "code-check"
                                                              (Summary
                                                                 "Check validity of a conversation code."
                                                               :> (Description
                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                   :> (CanThrow 'CodeNotFound
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidConversationPassword
                                                                               :> ("conversations"
                                                                                   :> ("code-check"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationCode
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Valid"]
                                                                                                ()))))))))
                                                            :<|> (Named
                                                                    "create-conversation-code-unqualified@v3"
                                                                    (Summary
                                                                       "Create or recreate a conversation code"
                                                                     :> (Until 'V4
                                                                         :> (DescriptionOAuthScope
                                                                               'WriteConversationsCode
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'CreateConversationCodeConflict
                                                                                             :> (ZUser
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                  :<|> (Named
                                                                          "create-conversation-code-unqualified"
                                                                          (Summary
                                                                             "Create or recreate a conversation code"
                                                                           :> (From 'V4
                                                                               :> (DescriptionOAuthScope
                                                                                     'WriteConversationsCode
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'CreateConversationCodeConflict
                                                                                                   :> (ZUser
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 CreateConversationCodeRequest
                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                        :<|> (Named
                                                                                "get-conversation-guest-links-status"
                                                                                (Summary
                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZUser
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("features"
                                                                                                         :> ("conversationGuestLinks"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     GuestLinksConfig)))))))))
                                                                              :<|> (Named
                                                                                      "remove-code-unqualified"
                                                                                      (Summary
                                                                                         "Delete conversation code"
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("code"
                                                                                                                   :> MultiVerb
                                                                                                                        'DELETE
                                                                                                                        '[JSON]
                                                                                                                        '[Respond
                                                                                                                            200
                                                                                                                            "Conversation code deleted."
                                                                                                                            Event]
                                                                                                                        Event))))))))
                                                                                    :<|> (Named
                                                                                            "get-code"
                                                                                            (Summary
                                                                                               "Get existing conversation code"
                                                                                             :> (CanThrow
                                                                                                   'CodeNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'GuestLinksDisabled
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[Respond
                                                                                                                                          200
                                                                                                                                          "Conversation Code"
                                                                                                                                          ConversationCodeInfo]
                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                          :<|> (Named
                                                                                                  "member-typing-unqualified"
                                                                                                  (Summary
                                                                                                     "Sending typing notifications"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "update-typing-indicator"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-typing-indicator-updated"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("typing"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             TypingStatus
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Notification sent"]
                                                                                                                                                ())))))))))))
                                                                                                :<|> (Named
                                                                                                        "member-typing-qualified"
                                                                                                        (Summary
                                                                                                           "Sending typing notifications"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "update-typing-indicator"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-typing-indicator-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("typing"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               TypingStatus
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "Notification sent"]
                                                                                                                                                  ()))))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-member-unqualified"
                                                                                                              (Summary
                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "leave-conversation"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (Until
                                                                                                                                     'V2
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                         "usr"
                                                                                                                                                                         UserId
                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-member"
                                                                                                                    (Summary
                                                                                                                       "Remove a member from a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "leave-conversation"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("members"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-other-member-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-other-member"
                                                                                                                                (Summary
                                                                                                                                   "Update membership of the specified user"
                                                                                                                                 :> (Description
                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                               "usr"
                                                                                                                                                                                               UserId
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                           Event)
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-one-to-one-conversation@v2"
        (Summary "Create a 1:1 conversation"
         :> (MakesFederatedCall 'Brig "api-version"
             :> (MakesFederatedCall 'Galley "on-conversation-created"
                 :> (Until 'V3
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NoBindingTeamMembers
                                 :> (CanThrow 'NonBindingTeam
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'NotConnected
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow UnreachableBackendsLegacy
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> ("one2one"
                                                                             :> (VersionedReqBody
                                                                                   'V2
                                                                                   '[JSON]
                                                                                   NewConv
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             200
                                                                                             "Conversation existed"
                                                                                             Conversation),
                                                                                        WithHeaders
                                                                                          ConversationHeaders
                                                                                          Conversation
                                                                                          (VersionedRespond
                                                                                             'V2
                                                                                             201
                                                                                             "Conversation created"
                                                                                             Conversation)]
                                                                                      (ResponseForExistedCreated
                                                                                         Conversation))))))))))))))))))))
      :<|> (Named
              "create-one-to-one-conversation"
              (Summary "Create a 1:1 conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-created"
                   :> (From 'V3
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'InvalidOperation
                               :> (CanThrow 'NoBindingTeamMembers
                                   :> (CanThrow 'NonBindingTeam
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'NotConnected
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (CanThrow 'MissingLegalholdConsent
                                                           :> (CanThrow UnreachableBackendsLegacy
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> ("one2one"
                                                                               :> (ReqBody
                                                                                     '[JSON] NewConv
                                                                                   :> MultiVerb
                                                                                        'POST
                                                                                        '[JSON]
                                                                                        '[WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V3
                                                                                               200
                                                                                               "Conversation existed"
                                                                                               Conversation),
                                                                                          WithHeaders
                                                                                            ConversationHeaders
                                                                                            Conversation
                                                                                            (VersionedRespond
                                                                                               'V3
                                                                                               201
                                                                                               "Conversation created"
                                                                                               Conversation)]
                                                                                        (ResponseForExistedCreated
                                                                                           Conversation)))))))))))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation@v5"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V5
                         :> (Until 'V6
                             :> (ZLocalUser
                                 :> (CanThrow 'MLSNotEnabled
                                     :> (CanThrow 'NotConnected
                                         :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                             :> ("conversations"
                                                 :> ("one2one"
                                                     :> (QualifiedCapture "usr" UserId
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[VersionedRespond
                                                                  'V5
                                                                  200
                                                                  "MLS 1-1 conversation"
                                                                  Conversation]
                                                              Conversation))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation@v6"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V6
                               :> (Until 'V7
                                   :> (ZLocalUser
                                       :> (CanThrow 'MLSNotEnabled
                                           :> (CanThrow 'NotConnected
                                               :> ("conversations"
                                                   :> ("one2one"
                                                       :> (QualifiedCapture "usr" UserId
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "MLS 1-1 conversation"
                                                                    (MLSOne2OneConversation
                                                                       MLSPublicKey)]
                                                                (MLSOne2OneConversation
                                                                   MLSPublicKey))))))))))
                        :<|> (Named
                                "get-one-to-one-mls-conversation"
                                (Summary "Get an MLS 1:1 conversation"
                                 :> (From 'V7
                                     :> (ZLocalUser
                                         :> (CanThrow 'MLSNotEnabled
                                             :> (CanThrow 'NotConnected
                                                 :> ("conversations"
                                                     :> ("one2one"
                                                         :> (QualifiedCapture "usr" UserId
                                                             :> (QueryParam
                                                                   "format" MLSPublicKeyFormat
                                                                 :> MultiVerb
                                                                      'GET
                                                                      '[JSON]
                                                                      '[Respond
                                                                          200
                                                                          "MLS 1-1 conversation"
                                                                          (MLSOne2OneConversation
                                                                             SomeKey)]
                                                                      (MLSOne2OneConversation
                                                                         SomeKey))))))))))
                              :<|> (Named
                                      "add-members-to-conversation-unqualified"
                                      (Summary
                                         "Add members to an existing conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (Until 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         Invite
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            ConvUpdateResponses
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation-unqualified2"
                                            (Summary
                                               "Add qualified members to an existing conversation."
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (Until 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> ("v2"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   InviteQualified
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      ConvUpdateResponses
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))))))))
                                          :<|> (Named
                                                  "add-members-to-conversation"
                                                  (Summary
                                                     "Add qualified members to an existing conversation."
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (From 'V2
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'AddConversationMember)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'LeaveConversation)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> (CanThrow
                                                                                     'TooManyMembers
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'NotConnected
                                                                                               :> (CanThrow
                                                                                                     'MissingLegalholdConsent
                                                                                                   :> (CanThrow
                                                                                                         NonFederatingBackends
                                                                                                       :> (CanThrow
                                                                                                             UnreachableBackends
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     InviteQualified
                                                                                                                                   :> MultiVerb
                                                                                                                                        'POST
                                                                                                                                        '[JSON]
                                                                                                                                        ConvUpdateResponses
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))))))))
                                                :<|> (Named
                                                        "join-conversation-by-id-unqualified"
                                                        (Summary
                                                           "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                         :> (Until 'V5
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TooManyMembers
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("join"
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvJoinResponses
                                                                                                              (UpdateResult
                                                                                                                 Event))))))))))))))
                                                      :<|> (Named
                                                              "join-conversation-by-code-unqualified"
                                                              (Summary
                                                                 "Join a conversation using a reusable code"
                                                               :> (Description
                                                                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (CanThrow 'CodeNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidConversationPassword
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'GuestLinksDisabled
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'NotATeamMember
                                                                                                   :> (CanThrow
                                                                                                         'TooManyMembers
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> ("join"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             JoinConversationByCode
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvJoinResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))
                                                            :<|> (Named
                                                                    "code-check"
                                                                    (Summary
                                                                       "Check validity of a conversation code."
                                                                     :> (Description
                                                                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                         :> (CanThrow 'CodeNotFound
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidConversationPassword
                                                                                     :> ("conversations"
                                                                                         :> ("code-check"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationCode
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Valid"]
                                                                                                      ()))))))))
                                                                  :<|> (Named
                                                                          "create-conversation-code-unqualified@v3"
                                                                          (Summary
                                                                             "Create or recreate a conversation code"
                                                                           :> (Until 'V4
                                                                               :> (DescriptionOAuthScope
                                                                                     'WriteConversationsCode
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'CreateConversationCodeConflict
                                                                                                   :> (ZUser
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> CreateConversationCodeVerb)))))))))))))
                                                                        :<|> (Named
                                                                                "create-conversation-code-unqualified"
                                                                                (Summary
                                                                                   "Create or recreate a conversation code"
                                                                                 :> (From 'V4
                                                                                     :> (DescriptionOAuthScope
                                                                                           'WriteConversationsCode
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'GuestLinksDisabled
                                                                                                     :> (CanThrow
                                                                                                           'CreateConversationCodeConflict
                                                                                                         :> (ZUser
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZOptConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       CreateConversationCodeRequest
                                                                                                                                     :> CreateConversationCodeVerb))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-guest-links-status"
                                                                                      (Summary
                                                                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZUser
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("features"
                                                                                                               :> ("conversationGuestLinks"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           GuestLinksConfig)))))))))
                                                                                    :<|> (Named
                                                                                            "remove-code-unqualified"
                                                                                            (Summary
                                                                                               "Delete conversation code"
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("code"
                                                                                                                         :> MultiVerb
                                                                                                                              'DELETE
                                                                                                                              '[JSON]
                                                                                                                              '[Respond
                                                                                                                                  200
                                                                                                                                  "Conversation code deleted."
                                                                                                                                  Event]
                                                                                                                              Event))))))))
                                                                                          :<|> (Named
                                                                                                  "get-code"
                                                                                                  (Summary
                                                                                                     "Get existing conversation code"
                                                                                                   :> (CanThrow
                                                                                                         'CodeNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'GuestLinksDisabled
                                                                                                                   :> (ZHostOpt
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("code"
                                                                                                                                       :> MultiVerb
                                                                                                                                            'GET
                                                                                                                                            '[JSON]
                                                                                                                                            '[Respond
                                                                                                                                                200
                                                                                                                                                "Conversation Code"
                                                                                                                                                ConversationCodeInfo]
                                                                                                                                            ConversationCodeInfo))))))))))
                                                                                                :<|> (Named
                                                                                                        "member-typing-unqualified"
                                                                                                        (Summary
                                                                                                           "Sending typing notifications"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "update-typing-indicator"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-typing-indicator-updated"
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("typing"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   TypingStatus
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'POST
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Notification sent"]
                                                                                                                                                      ())))))))))))
                                                                                                      :<|> (Named
                                                                                                              "member-typing-qualified"
                                                                                                              (Summary
                                                                                                                 "Sending typing notifications"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "update-typing-indicator"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-typing-indicator-updated"
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("typing"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     TypingStatus
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'POST
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "Notification sent"]
                                                                                                                                                        ()))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-member-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Remove a member from a conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "leave-conversation"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (Until
                                                                                                                                           'V2
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("members"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                               "usr"
                                                                                                                                                                               UserId
                                                                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "remove-member"
                                                                                                                          (Summary
                                                                                                                             "Remove a member from a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "leave-conversation"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("members"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-other-member-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update membership of the specified user (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidTarget
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("members"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                                   "usr"
                                                                                                                                                                                                   UserId
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                                          ()))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-other-member"
                                                                                                                                      (Summary
                                                                                                                                         "Update membership of the specified user"
                                                                                                                                       :> (Description
                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-conversation-updated"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvMemberNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidTarget
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("members"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                                                     "usr"
                                                                                                                                                                                                     UserId
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                200
                                                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                                                            ())))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name-deprecated"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationName)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("name"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-name"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update conversation name"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Brig
                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-message-timer"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update the message timer for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "update-conversation"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Galley
                                                                                                                                                                                               "update-conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Brig
                                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-access"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                                         'Galley
                                                                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                                             'Galley
                                                                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                                 'Brig
                                                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                                                               :> (From
                                                                                                                                                                                                                     'V3
                                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (Maybe
                                                                                                                                                                                                                                     Member)))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                                                                               :> (Deprecated
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                                                              200
                                                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                                                                          :> (From
                                                                                                                                                                                                                                'V5
                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-one-to-one-conversation" (((HasAnnotation 'Remote "galley" "on-conversation-created",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> NewConv
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NoBindingTeamMembers ()),
        Error (Tagged 'NonBindingTeam ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
        Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (ResponseForExistedCreated Conversation))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-created")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-created",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ResponseForExistedCreated Conversation)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> NewConv
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NoBindingTeamMembers ()),
       Error (Tagged 'NonBindingTeam ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error UnreachableBackendsLegacy, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (ConversationResponse Conversation)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r, Member (Error InvalidInput) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'NonBindingTeam ())) r,
 Member (Error (Tagged 'NoBindingTeamMembers ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error UnreachableBackendsLegacy) r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> NewConv -> Sem r (ConversationResponse Conversation)
createOne2OneConversation)
    API
  (Named
     "create-one-to-one-conversation"
     (Summary "Create a 1:1 conversation"
      :> (MakesFederatedCall 'Galley "on-conversation-created"
          :> (From 'V3
              :> (CanThrow 'ConvAccessDenied
                  :> (CanThrow 'InvalidOperation
                      :> (CanThrow 'NoBindingTeamMembers
                          :> (CanThrow 'NonBindingTeam
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'NotConnected
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow 'MissingLegalholdConsent
                                                  :> (CanThrow UnreachableBackendsLegacy
                                                      :> (ZLocalUser
                                                          :> (ZConn
                                                              :> ("conversations"
                                                                  :> ("one2one"
                                                                      :> (ReqBody '[JSON] NewConv
                                                                          :> MultiVerb
                                                                               'POST
                                                                               '[JSON]
                                                                               '[WithHeaders
                                                                                   ConversationHeaders
                                                                                   Conversation
                                                                                   (VersionedRespond
                                                                                      'V3
                                                                                      200
                                                                                      "Conversation existed"
                                                                                      Conversation),
                                                                                 WithHeaders
                                                                                   ConversationHeaders
                                                                                   Conversation
                                                                                   (VersionedRespond
                                                                                      'V3
                                                                                      201
                                                                                      "Conversation created"
                                                                                      Conversation)]
                                                                               (ResponseForExistedCreated
                                                                                  Conversation))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation@v5"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V5
             :> (Until 'V6
                 :> (ZLocalUser
                     :> (CanThrow 'MLSNotEnabled
                         :> (CanThrow 'NotConnected
                             :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                 :> ("conversations"
                                     :> ("one2one"
                                         :> (QualifiedCapture "usr" UserId
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[VersionedRespond
                                                      'V5 200 "MLS 1-1 conversation" Conversation]
                                                  Conversation))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation@v6"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V6
                   :> (Until 'V7
                       :> (ZLocalUser
                           :> (CanThrow 'MLSNotEnabled
                               :> (CanThrow 'NotConnected
                                   :> ("conversations"
                                       :> ("one2one"
                                           :> (QualifiedCapture "usr" UserId
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "MLS 1-1 conversation"
                                                        (MLSOne2OneConversation MLSPublicKey)]
                                                    (MLSOne2OneConversation MLSPublicKey))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V7
                         :> (ZLocalUser
                             :> (CanThrow 'MLSNotEnabled
                                 :> (CanThrow 'NotConnected
                                     :> ("conversations"
                                         :> ("one2one"
                                             :> (QualifiedCapture "usr" UserId
                                                 :> (QueryParam "format" MLSPublicKeyFormat
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "MLS 1-1 conversation"
                                                              (MLSOne2OneConversation SomeKey)]
                                                          (MLSOne2OneConversation SomeKey))))))))))
                  :<|> (Named
                          "add-members-to-conversation-unqualified"
                          (Summary "Add members to an existing conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (Until 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             Invite
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                ConvUpdateResponses
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))))))))
                        :<|> (Named
                                "add-members-to-conversation-unqualified2"
                                (Summary "Add qualified members to an existing conversation."
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (Until 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> ("v2"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       InviteQualified
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvUpdateResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))))))))
                              :<|> (Named
                                      "add-members-to-conversation"
                                      (Summary "Add qualified members to an existing conversation."
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (From 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         InviteQualified
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            ConvUpdateResponses
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))))))))
                                    :<|> (Named
                                            "join-conversation-by-id-unqualified"
                                            (Summary
                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                             :> (Until 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TooManyMembers
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("join"
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvJoinResponses
                                                                                                  (UpdateResult
                                                                                                     Event))))))))))))))
                                          :<|> (Named
                                                  "join-conversation-by-code-unqualified"
                                                  (Summary
                                                     "Join a conversation using a reusable code"
                                                   :> (Description
                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (CanThrow 'CodeNotFound
                                                               :> (CanThrow
                                                                     'InvalidConversationPassword
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'GuestLinksDisabled
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TooManyMembers
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> ("join"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 JoinConversationByCode
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvJoinResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))
                                                :<|> (Named
                                                        "code-check"
                                                        (Summary
                                                           "Check validity of a conversation code."
                                                         :> (Description
                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                             :> (CanThrow 'CodeNotFound
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'InvalidConversationPassword
                                                                         :> ("conversations"
                                                                             :> ("code-check"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationCode
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Valid"]
                                                                                          ()))))))))
                                                      :<|> (Named
                                                              "create-conversation-code-unqualified@v3"
                                                              (Summary
                                                                 "Create or recreate a conversation code"
                                                               :> (Until 'V4
                                                                   :> (DescriptionOAuthScope
                                                                         'WriteConversationsCode
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'CreateConversationCodeConflict
                                                                                       :> (ZUser
                                                                                           :> (ZHostOpt
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                            :<|> (Named
                                                                    "create-conversation-code-unqualified"
                                                                    (Summary
                                                                       "Create or recreate a conversation code"
                                                                     :> (From 'V4
                                                                         :> (DescriptionOAuthScope
                                                                               'WriteConversationsCode
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'CreateConversationCodeConflict
                                                                                             :> (ZUser
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           CreateConversationCodeRequest
                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                  :<|> (Named
                                                                          "get-conversation-guest-links-status"
                                                                          (Summary
                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZUser
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("features"
                                                                                                   :> ("conversationGuestLinks"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               GuestLinksConfig)))))))))
                                                                        :<|> (Named
                                                                                "remove-code-unqualified"
                                                                                (Summary
                                                                                   "Delete conversation code"
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("code"
                                                                                                             :> MultiVerb
                                                                                                                  'DELETE
                                                                                                                  '[JSON]
                                                                                                                  '[Respond
                                                                                                                      200
                                                                                                                      "Conversation code deleted."
                                                                                                                      Event]
                                                                                                                  Event))))))))
                                                                              :<|> (Named
                                                                                      "get-code"
                                                                                      (Summary
                                                                                         "Get existing conversation code"
                                                                                       :> (CanThrow
                                                                                             'CodeNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'GuestLinksDisabled
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[Respond
                                                                                                                                    200
                                                                                                                                    "Conversation Code"
                                                                                                                                    ConversationCodeInfo]
                                                                                                                                ConversationCodeInfo))))))))))
                                                                                    :<|> (Named
                                                                                            "member-typing-unqualified"
                                                                                            (Summary
                                                                                               "Sending typing notifications"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "update-typing-indicator"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-typing-indicator-updated"
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("typing"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       TypingStatus
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Notification sent"]
                                                                                                                                          ())))))))))))
                                                                                          :<|> (Named
                                                                                                  "member-typing-qualified"
                                                                                                  (Summary
                                                                                                     "Sending typing notifications"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "update-typing-indicator"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-typing-indicator-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("typing"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         TypingStatus
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "Notification sent"]
                                                                                                                                            ()))))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-member-unqualified"
                                                                                                        (Summary
                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "leave-conversation"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (Until
                                                                                                                               'V2
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                   "usr"
                                                                                                                                                                   UserId
                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-member"
                                                                                                              (Summary
                                                                                                                 "Remove a member from a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "leave-conversation"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'RemoveConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("members"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-other-member-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("members"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-other-member"
                                                                                                                          (Summary
                                                                                                                             "Update membership of the specified user"
                                                                                                                           :> (Description
                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("members"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                         "usr"
                                                                                                                                                                                         UserId
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                     Event)
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-one-to-one-conversation"
        (Summary "Create a 1:1 conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-created"
             :> (From 'V3
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'InvalidOperation
                         :> (CanThrow 'NoBindingTeamMembers
                             :> (CanThrow 'NonBindingTeam
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'NotConnected
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow 'MissingLegalholdConsent
                                                     :> (CanThrow UnreachableBackendsLegacy
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> ("one2one"
                                                                         :> (ReqBody '[JSON] NewConv
                                                                             :> MultiVerb
                                                                                  'POST
                                                                                  '[JSON]
                                                                                  '[WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V3
                                                                                         200
                                                                                         "Conversation existed"
                                                                                         Conversation),
                                                                                    WithHeaders
                                                                                      ConversationHeaders
                                                                                      Conversation
                                                                                      (VersionedRespond
                                                                                         'V3
                                                                                         201
                                                                                         "Conversation created"
                                                                                         Conversation)]
                                                                                  (ResponseForExistedCreated
                                                                                     Conversation)))))))))))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation@v5"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V5
                   :> (Until 'V6
                       :> (ZLocalUser
                           :> (CanThrow 'MLSNotEnabled
                               :> (CanThrow 'NotConnected
                                   :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                       :> ("conversations"
                                           :> ("one2one"
                                               :> (QualifiedCapture "usr" UserId
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[VersionedRespond
                                                            'V5
                                                            200
                                                            "MLS 1-1 conversation"
                                                            Conversation]
                                                        Conversation))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation@v6"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V6
                         :> (Until 'V7
                             :> (ZLocalUser
                                 :> (CanThrow 'MLSNotEnabled
                                     :> (CanThrow 'NotConnected
                                         :> ("conversations"
                                             :> ("one2one"
                                                 :> (QualifiedCapture "usr" UserId
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "MLS 1-1 conversation"
                                                              (MLSOne2OneConversation MLSPublicKey)]
                                                          (MLSOne2OneConversation
                                                             MLSPublicKey))))))))))
                  :<|> (Named
                          "get-one-to-one-mls-conversation"
                          (Summary "Get an MLS 1:1 conversation"
                           :> (From 'V7
                               :> (ZLocalUser
                                   :> (CanThrow 'MLSNotEnabled
                                       :> (CanThrow 'NotConnected
                                           :> ("conversations"
                                               :> ("one2one"
                                                   :> (QualifiedCapture "usr" UserId
                                                       :> (QueryParam "format" MLSPublicKeyFormat
                                                           :> MultiVerb
                                                                'GET
                                                                '[JSON]
                                                                '[Respond
                                                                    200
                                                                    "MLS 1-1 conversation"
                                                                    (MLSOne2OneConversation
                                                                       SomeKey)]
                                                                (MLSOne2OneConversation
                                                                   SomeKey))))))))))
                        :<|> (Named
                                "add-members-to-conversation-unqualified"
                                (Summary "Add members to an existing conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (Until 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   Invite
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      ConvUpdateResponses
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))))))))
                              :<|> (Named
                                      "add-members-to-conversation-unqualified2"
                                      (Summary "Add qualified members to an existing conversation."
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (Until 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> ("v2"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             InviteQualified
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                ConvUpdateResponses
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))))))))
                                    :<|> (Named
                                            "add-members-to-conversation"
                                            (Summary
                                               "Add qualified members to an existing conversation."
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (From 'V2
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'AddConversationMember)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'LeaveConversation)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> (CanThrow
                                                                               'TooManyMembers
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'NotConnected
                                                                                         :> (CanThrow
                                                                                               'MissingLegalholdConsent
                                                                                             :> (CanThrow
                                                                                                   NonFederatingBackends
                                                                                                 :> (CanThrow
                                                                                                       UnreachableBackends
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               InviteQualified
                                                                                                                             :> MultiVerb
                                                                                                                                  'POST
                                                                                                                                  '[JSON]
                                                                                                                                  ConvUpdateResponses
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))))))))
                                          :<|> (Named
                                                  "join-conversation-by-id-unqualified"
                                                  (Summary
                                                     "Join a conversation by its ID (if link access enabled) (deprecated)"
                                                   :> (Until 'V5
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TooManyMembers
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("join"
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvJoinResponses
                                                                                                        (UpdateResult
                                                                                                           Event))))))))))))))
                                                :<|> (Named
                                                        "join-conversation-by-code-unqualified"
                                                        (Summary
                                                           "Join a conversation using a reusable code"
                                                         :> (Description
                                                               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (CanThrow 'CodeNotFound
                                                                     :> (CanThrow
                                                                           'InvalidConversationPassword
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'GuestLinksDisabled
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   'TooManyMembers
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> ("join"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       JoinConversationByCode
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvJoinResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))
                                                      :<|> (Named
                                                              "code-check"
                                                              (Summary
                                                                 "Check validity of a conversation code."
                                                               :> (Description
                                                                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                                   :> (CanThrow 'CodeNotFound
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidConversationPassword
                                                                               :> ("conversations"
                                                                                   :> ("code-check"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationCode
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Valid"]
                                                                                                ()))))))))
                                                            :<|> (Named
                                                                    "create-conversation-code-unqualified@v3"
                                                                    (Summary
                                                                       "Create or recreate a conversation code"
                                                                     :> (Until 'V4
                                                                         :> (DescriptionOAuthScope
                                                                               'WriteConversationsCode
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'CreateConversationCodeConflict
                                                                                             :> (ZUser
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> CreateConversationCodeVerb)))))))))))))
                                                                  :<|> (Named
                                                                          "create-conversation-code-unqualified"
                                                                          (Summary
                                                                             "Create or recreate a conversation code"
                                                                           :> (From 'V4
                                                                               :> (DescriptionOAuthScope
                                                                                     'WriteConversationsCode
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'GuestLinksDisabled
                                                                                               :> (CanThrow
                                                                                                     'CreateConversationCodeConflict
                                                                                                   :> (ZUser
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZOptConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 CreateConversationCodeRequest
                                                                                                                               :> CreateConversationCodeVerb))))))))))))))
                                                                        :<|> (Named
                                                                                "get-conversation-guest-links-status"
                                                                                (Summary
                                                                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZUser
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("features"
                                                                                                         :> ("conversationGuestLinks"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     GuestLinksConfig)))))))))
                                                                              :<|> (Named
                                                                                      "remove-code-unqualified"
                                                                                      (Summary
                                                                                         "Delete conversation code"
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("code"
                                                                                                                   :> MultiVerb
                                                                                                                        'DELETE
                                                                                                                        '[JSON]
                                                                                                                        '[Respond
                                                                                                                            200
                                                                                                                            "Conversation code deleted."
                                                                                                                            Event]
                                                                                                                        Event))))))))
                                                                                    :<|> (Named
                                                                                            "get-code"
                                                                                            (Summary
                                                                                               "Get existing conversation code"
                                                                                             :> (CanThrow
                                                                                                   'CodeNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'GuestLinksDisabled
                                                                                                             :> (ZHostOpt
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("code"
                                                                                                                                 :> MultiVerb
                                                                                                                                      'GET
                                                                                                                                      '[JSON]
                                                                                                                                      '[Respond
                                                                                                                                          200
                                                                                                                                          "Conversation Code"
                                                                                                                                          ConversationCodeInfo]
                                                                                                                                      ConversationCodeInfo))))))))))
                                                                                          :<|> (Named
                                                                                                  "member-typing-unqualified"
                                                                                                  (Summary
                                                                                                     "Sending typing notifications"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "update-typing-indicator"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-typing-indicator-updated"
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("typing"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             TypingStatus
                                                                                                                                           :> MultiVerb
                                                                                                                                                'POST
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Notification sent"]
                                                                                                                                                ())))))))))))
                                                                                                :<|> (Named
                                                                                                        "member-typing-qualified"
                                                                                                        (Summary
                                                                                                           "Sending typing notifications"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "update-typing-indicator"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-typing-indicator-updated"
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("typing"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               TypingStatus
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'POST
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "Notification sent"]
                                                                                                                                                  ()))))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-member-unqualified"
                                                                                                              (Summary
                                                                                                                 "Remove a member from a conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "leave-conversation"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (Until
                                                                                                                                     'V2
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("members"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                         "usr"
                                                                                                                                                                         UserId
                                                                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "remove-member"
                                                                                                                    (Summary
                                                                                                                       "Remove a member from a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "leave-conversation"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("members"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-other-member-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update membership of the specified user (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidTarget
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("members"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                                             "usr"
                                                                                                                                                                                             UserId
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                                    ()))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-other-member"
                                                                                                                                (Summary
                                                                                                                                   "Update membership of the specified user"
                                                                                                                                 :> (Description
                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-conversation-updated"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-mls-message-sent"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvMemberNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidTarget
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("members"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Target User ID"]
                                                                                                                                                                                               "usr"
                                                                                                                                                                                               UserId
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                          200
                                                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                                                      ())))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name-deprecated"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationRename
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationName)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("name"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-name"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update conversation name"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("name"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                                           Event)
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Brig
                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                             Event)))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-message-timer"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update the message timer for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "update-conversation"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Galley
                                                                                                                                                                                         "update-conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Brig
                                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-access"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                                   'Galley
                                                                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                                       'Galley
                                                                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                                           'Brig
                                                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                                                         :> (From
                                                                                                                                                                                                               'V3
                                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (Maybe
                                                                                                                                                                                                                               Member)))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                                                                         :> (Deprecated
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              "update-conversation-self"
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                                                        200
                                                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                                                    ())))))))))
                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                                                                    :> (From
                                                                                                                                                                                                                          'V5
                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-one-to-one-mls-conversation@v5" ServerT
  (Summary "Get an MLS 1:1 conversation"
   :> (From 'V5
       :> (Until 'V6
           :> (ZLocalUser
               :> (CanThrow 'MLSNotEnabled
                   :> (CanThrow 'NotConnected
                       :> (CanThrow 'MLSFederatedOne2OneNotSupported
                           :> ("conversations"
                               :> ("one2one"
                                   :> (QualifiedCapture "usr" UserId
                                       :> MultiVerb
                                            'GET
                                            '[JSON]
                                            '[VersionedRespond
                                                'V5 200 "MLS 1-1 conversation" Conversation]
                                            Conversation))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get an MLS 1:1 conversation"
            :> (From 'V5
                :> (Until 'V6
                    :> (ZLocalUser
                        :> (CanThrow 'MLSNotEnabled
                            :> (CanThrow 'NotConnected
                                :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                    :> ("conversations"
                                        :> ("one2one"
                                            :> (QualifiedCapture "usr" UserId
                                                :> MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[VersionedRespond
                                                         'V5
                                                         200
                                                         "MLS 1-1 conversation"
                                                         Conversation]
                                                     Conversation)))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Qualified UserId
-> Sem
     '[Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'NotConnected ()),
       Error (Tagged 'MLSFederatedOne2OneNotSupported ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Conversation
forall (r :: EffectRow).
(Member BrigAccess r, Member ConversationStore r,
 Member (Input Env) r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'MLSFederatedOne2OneNotSupported ())) r,
 Member FederatorAccess r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified UserId -> Sem r Conversation
getMLSOne2OneConversationV5
    API
  (Named
     "get-one-to-one-mls-conversation@v5"
     (Summary "Get an MLS 1:1 conversation"
      :> (From 'V5
          :> (Until 'V6
              :> (ZLocalUser
                  :> (CanThrow 'MLSNotEnabled
                      :> (CanThrow 'NotConnected
                          :> (CanThrow 'MLSFederatedOne2OneNotSupported
                              :> ("conversations"
                                  :> ("one2one"
                                      :> (QualifiedCapture "usr" UserId
                                          :> MultiVerb
                                               'GET
                                               '[JSON]
                                               '[VersionedRespond
                                                   'V5 200 "MLS 1-1 conversation" Conversation]
                                               Conversation)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation@v6"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V6
             :> (Until 'V7
                 :> (ZLocalUser
                     :> (CanThrow 'MLSNotEnabled
                         :> (CanThrow 'NotConnected
                             :> ("conversations"
                                 :> ("one2one"
                                     :> (QualifiedCapture "usr" UserId
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200
                                                  "MLS 1-1 conversation"
                                                  (MLSOne2OneConversation MLSPublicKey)]
                                              (MLSOne2OneConversation MLSPublicKey))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V7
                   :> (ZLocalUser
                       :> (CanThrow 'MLSNotEnabled
                           :> (CanThrow 'NotConnected
                               :> ("conversations"
                                   :> ("one2one"
                                       :> (QualifiedCapture "usr" UserId
                                           :> (QueryParam "format" MLSPublicKeyFormat
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "MLS 1-1 conversation"
                                                        (MLSOne2OneConversation SomeKey)]
                                                    (MLSOne2OneConversation SomeKey))))))))))
            :<|> (Named
                    "add-members-to-conversation-unqualified"
                    (Summary "Add members to an existing conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (Until 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       Invite
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          ConvUpdateResponses
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))))))))
                  :<|> (Named
                          "add-members-to-conversation-unqualified2"
                          (Summary "Add qualified members to an existing conversation."
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (Until 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> ("v2"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 InviteQualified
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvUpdateResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))))))))
                        :<|> (Named
                                "add-members-to-conversation"
                                (Summary "Add qualified members to an existing conversation."
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (From 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   InviteQualified
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      ConvUpdateResponses
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))))))))
                              :<|> (Named
                                      "join-conversation-by-id-unqualified"
                                      (Summary
                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                       :> (Until 'V5
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TooManyMembers
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("join"
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            ConvJoinResponses
                                                                                            (UpdateResult
                                                                                               Event))))))))))))))
                                    :<|> (Named
                                            "join-conversation-by-code-unqualified"
                                            (Summary "Join a conversation using a reusable code"
                                             :> (Description
                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (CanThrow 'CodeNotFound
                                                         :> (CanThrow 'InvalidConversationPassword
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'GuestLinksDisabled
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TooManyMembers
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> ("join"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           JoinConversationByCode
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvJoinResponses
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))
                                          :<|> (Named
                                                  "code-check"
                                                  (Summary "Check validity of a conversation code."
                                                   :> (Description
                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                       :> (CanThrow 'CodeNotFound
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow
                                                                     'InvalidConversationPassword
                                                                   :> ("conversations"
                                                                       :> ("code-check"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationCode
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200 "Valid"]
                                                                                    ()))))))))
                                                :<|> (Named
                                                        "create-conversation-code-unqualified@v3"
                                                        (Summary
                                                           "Create or recreate a conversation code"
                                                         :> (Until 'V4
                                                             :> (DescriptionOAuthScope
                                                                   'WriteConversationsCode
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'CreateConversationCodeConflict
                                                                                 :> (ZUser
                                                                                     :> (ZHostOpt
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                      :<|> (Named
                                                              "create-conversation-code-unqualified"
                                                              (Summary
                                                                 "Create or recreate a conversation code"
                                                               :> (From 'V4
                                                                   :> (DescriptionOAuthScope
                                                                         'WriteConversationsCode
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'CreateConversationCodeConflict
                                                                                       :> (ZUser
                                                                                           :> (ZHostOpt
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     CreateConversationCodeRequest
                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                            :<|> (Named
                                                                    "get-conversation-guest-links-status"
                                                                    (Summary
                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZUser
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("features"
                                                                                             :> ("conversationGuestLinks"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         GuestLinksConfig)))))))))
                                                                  :<|> (Named
                                                                          "remove-code-unqualified"
                                                                          (Summary
                                                                             "Delete conversation code"
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("code"
                                                                                                       :> MultiVerb
                                                                                                            'DELETE
                                                                                                            '[JSON]
                                                                                                            '[Respond
                                                                                                                200
                                                                                                                "Conversation code deleted."
                                                                                                                Event]
                                                                                                            Event))))))))
                                                                        :<|> (Named
                                                                                "get-code"
                                                                                (Summary
                                                                                   "Get existing conversation code"
                                                                                 :> (CanThrow
                                                                                       'CodeNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'GuestLinksDisabled
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[Respond
                                                                                                                              200
                                                                                                                              "Conversation Code"
                                                                                                                              ConversationCodeInfo]
                                                                                                                          ConversationCodeInfo))))))))))
                                                                              :<|> (Named
                                                                                      "member-typing-unqualified"
                                                                                      (Summary
                                                                                         "Sending typing notifications"
                                                                                       :> (Until 'V3
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "update-typing-indicator"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-typing-indicator-updated"
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("typing"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 TypingStatus
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Notification sent"]
                                                                                                                                    ())))))))))))
                                                                                    :<|> (Named
                                                                                            "member-typing-qualified"
                                                                                            (Summary
                                                                                               "Sending typing notifications"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "update-typing-indicator"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-typing-indicator-updated"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("typing"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   TypingStatus
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "Notification sent"]
                                                                                                                                      ()))))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-member-unqualified"
                                                                                                  (Summary
                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "leave-conversation"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (Until
                                                                                                                         'V2
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Target User ID"]
                                                                                                                                                             "usr"
                                                                                                                                                             UserId
                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-member"
                                                                                                        (Summary
                                                                                                           "Remove a member from a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "leave-conversation"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'RemoveConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("members"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Target User ID"]
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-other-member-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidTarget
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("members"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                            200
                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-other-member"
                                                                                                                    (Summary
                                                                                                                       "Update membership of the specified user"
                                                                                                                     :> (Description
                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidTarget
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("members"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                   "usr"
                                                                                                                                                                                   UserId
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationRename
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("name"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                               Event)
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "update-conversation"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "update-conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                              'V5
                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation@v5"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V5
             :> (Until 'V6
                 :> (ZLocalUser
                     :> (CanThrow 'MLSNotEnabled
                         :> (CanThrow 'NotConnected
                             :> (CanThrow 'MLSFederatedOne2OneNotSupported
                                 :> ("conversations"
                                     :> ("one2one"
                                         :> (QualifiedCapture "usr" UserId
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[VersionedRespond
                                                      'V5 200 "MLS 1-1 conversation" Conversation]
                                                  Conversation))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation@v6"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V6
                   :> (Until 'V7
                       :> (ZLocalUser
                           :> (CanThrow 'MLSNotEnabled
                               :> (CanThrow 'NotConnected
                                   :> ("conversations"
                                       :> ("one2one"
                                           :> (QualifiedCapture "usr" UserId
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "MLS 1-1 conversation"
                                                        (MLSOne2OneConversation MLSPublicKey)]
                                                    (MLSOne2OneConversation MLSPublicKey))))))))))
            :<|> (Named
                    "get-one-to-one-mls-conversation"
                    (Summary "Get an MLS 1:1 conversation"
                     :> (From 'V7
                         :> (ZLocalUser
                             :> (CanThrow 'MLSNotEnabled
                                 :> (CanThrow 'NotConnected
                                     :> ("conversations"
                                         :> ("one2one"
                                             :> (QualifiedCapture "usr" UserId
                                                 :> (QueryParam "format" MLSPublicKeyFormat
                                                     :> MultiVerb
                                                          'GET
                                                          '[JSON]
                                                          '[Respond
                                                              200
                                                              "MLS 1-1 conversation"
                                                              (MLSOne2OneConversation SomeKey)]
                                                          (MLSOne2OneConversation SomeKey))))))))))
                  :<|> (Named
                          "add-members-to-conversation-unqualified"
                          (Summary "Add members to an existing conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (Until 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             Invite
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                ConvUpdateResponses
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))))))))
                        :<|> (Named
                                "add-members-to-conversation-unqualified2"
                                (Summary "Add qualified members to an existing conversation."
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (Until 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> ("v2"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       InviteQualified
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          ConvUpdateResponses
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))))))))
                              :<|> (Named
                                      "add-members-to-conversation"
                                      (Summary "Add qualified members to an existing conversation."
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (From 'V2
                                                   :> (CanThrow
                                                         ('ActionDenied 'AddConversationMember)
                                                       :> (CanThrow
                                                             ('ActionDenied 'LeaveConversation)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> (CanThrow 'TooManyMembers
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'NotConnected
                                                                                   :> (CanThrow
                                                                                         'MissingLegalholdConsent
                                                                                       :> (CanThrow
                                                                                             NonFederatingBackends
                                                                                           :> (CanThrow
                                                                                                 UnreachableBackends
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         InviteQualified
                                                                                                                       :> MultiVerb
                                                                                                                            'POST
                                                                                                                            '[JSON]
                                                                                                                            ConvUpdateResponses
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))))))))
                                    :<|> (Named
                                            "join-conversation-by-id-unqualified"
                                            (Summary
                                               "Join a conversation by its ID (if link access enabled) (deprecated)"
                                             :> (Until 'V5
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TooManyMembers
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("join"
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvJoinResponses
                                                                                                  (UpdateResult
                                                                                                     Event))))))))))))))
                                          :<|> (Named
                                                  "join-conversation-by-code-unqualified"
                                                  (Summary
                                                     "Join a conversation using a reusable code"
                                                   :> (Description
                                                         "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (CanThrow 'CodeNotFound
                                                               :> (CanThrow
                                                                     'InvalidConversationPassword
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'GuestLinksDisabled
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'NotATeamMember
                                                                                       :> (CanThrow
                                                                                             'TooManyMembers
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> ("join"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 JoinConversationByCode
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvJoinResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))
                                                :<|> (Named
                                                        "code-check"
                                                        (Summary
                                                           "Check validity of a conversation code."
                                                         :> (Description
                                                               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                             :> (CanThrow 'CodeNotFound
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'InvalidConversationPassword
                                                                         :> ("conversations"
                                                                             :> ("code-check"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationCode
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Valid"]
                                                                                          ()))))))))
                                                      :<|> (Named
                                                              "create-conversation-code-unqualified@v3"
                                                              (Summary
                                                                 "Create or recreate a conversation code"
                                                               :> (Until 'V4
                                                                   :> (DescriptionOAuthScope
                                                                         'WriteConversationsCode
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'CreateConversationCodeConflict
                                                                                       :> (ZUser
                                                                                           :> (ZHostOpt
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> CreateConversationCodeVerb)))))))))))))
                                                            :<|> (Named
                                                                    "create-conversation-code-unqualified"
                                                                    (Summary
                                                                       "Create or recreate a conversation code"
                                                                     :> (From 'V4
                                                                         :> (DescriptionOAuthScope
                                                                               'WriteConversationsCode
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'GuestLinksDisabled
                                                                                         :> (CanThrow
                                                                                               'CreateConversationCodeConflict
                                                                                             :> (ZUser
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZOptConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           CreateConversationCodeRequest
                                                                                                                         :> CreateConversationCodeVerb))))))))))))))
                                                                  :<|> (Named
                                                                          "get-conversation-guest-links-status"
                                                                          (Summary
                                                                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZUser
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("features"
                                                                                                   :> ("conversationGuestLinks"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               GuestLinksConfig)))))))))
                                                                        :<|> (Named
                                                                                "remove-code-unqualified"
                                                                                (Summary
                                                                                   "Delete conversation code"
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("code"
                                                                                                             :> MultiVerb
                                                                                                                  'DELETE
                                                                                                                  '[JSON]
                                                                                                                  '[Respond
                                                                                                                      200
                                                                                                                      "Conversation code deleted."
                                                                                                                      Event]
                                                                                                                  Event))))))))
                                                                              :<|> (Named
                                                                                      "get-code"
                                                                                      (Summary
                                                                                         "Get existing conversation code"
                                                                                       :> (CanThrow
                                                                                             'CodeNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'GuestLinksDisabled
                                                                                                       :> (ZHostOpt
                                                                                                           :> (ZLocalUser
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("code"
                                                                                                                           :> MultiVerb
                                                                                                                                'GET
                                                                                                                                '[JSON]
                                                                                                                                '[Respond
                                                                                                                                    200
                                                                                                                                    "Conversation Code"
                                                                                                                                    ConversationCodeInfo]
                                                                                                                                ConversationCodeInfo))))))))))
                                                                                    :<|> (Named
                                                                                            "member-typing-unqualified"
                                                                                            (Summary
                                                                                               "Sending typing notifications"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "update-typing-indicator"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-typing-indicator-updated"
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("typing"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       TypingStatus
                                                                                                                                     :> MultiVerb
                                                                                                                                          'POST
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Notification sent"]
                                                                                                                                          ())))))))))))
                                                                                          :<|> (Named
                                                                                                  "member-typing-qualified"
                                                                                                  (Summary
                                                                                                     "Sending typing notifications"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "update-typing-indicator"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-typing-indicator-updated"
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("typing"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         TypingStatus
                                                                                                                                       :> MultiVerb
                                                                                                                                            'POST
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "Notification sent"]
                                                                                                                                            ()))))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-member-unqualified"
                                                                                                        (Summary
                                                                                                           "Remove a member from a conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "leave-conversation"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (Until
                                                                                                                               'V2
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("members"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                   "usr"
                                                                                                                                                                   UserId
                                                                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "remove-member"
                                                                                                              (Summary
                                                                                                                 "Remove a member from a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "leave-conversation"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'RemoveConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("members"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-other-member-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update membership of the specified user (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvMemberNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidTarget
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("members"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                                       "usr"
                                                                                                                                                                                       UserId
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                                              ()))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-other-member"
                                                                                                                          (Summary
                                                                                                                             "Update membership of the specified user"
                                                                                                                           :> (Description
                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-conversation-updated"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-mls-message-sent"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvMemberNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidTarget
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("members"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Target User ID"]
                                                                                                                                                                                         "usr"
                                                                                                                                                                                         UserId
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                    200
                                                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                                                ())))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name-deprecated"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationRename
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                                             "Name updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationName)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("name"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationRename
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-name"
                                                                                                                                            (Summary
                                                                                                                                               "Update conversation name"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationName)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("name"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConversationRename
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                                     Event)
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Brig
                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                       Event)))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-message-timer"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update the message timer for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "update-conversation"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Galley
                                                                                                                                                                                   "update-conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Brig
                                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access@v2"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-access"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                                             'Galley
                                                                                                                                                                                             "on-conversation-updated"
                                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                                 'Galley
                                                                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                                     'Brig
                                                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                                                   :> (From
                                                                                                                                                                                                         'V3
                                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (Maybe
                                                                                                                                                                                                                         Member)))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                                                                   :> (Deprecated
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                                            ()))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        "update-conversation-self"
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "Update self membership properties"
                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                                                  200
                                                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                                                              ())))))))))
                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                                                                              :> (From
                                                                                                                                                                                                                    'V5
                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-one-to-one-mls-conversation@v6" ServerT
  (Summary "Get an MLS 1:1 conversation"
   :> (From 'V6
       :> (Until 'V7
           :> (ZLocalUser
               :> (CanThrow 'MLSNotEnabled
                   :> (CanThrow 'NotConnected
                       :> ("conversations"
                           :> ("one2one"
                               :> (QualifiedCapture "usr" UserId
                                   :> MultiVerb
                                        'GET
                                        '[JSON]
                                        '[Respond
                                            200
                                            "MLS 1-1 conversation"
                                            (MLSOne2OneConversation MLSPublicKey)]
                                        (MLSOne2OneConversation MLSPublicKey))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get an MLS 1:1 conversation"
            :> (From 'V6
                :> (Until 'V7
                    :> (ZLocalUser
                        :> (CanThrow 'MLSNotEnabled
                            :> (CanThrow 'NotConnected
                                :> ("conversations"
                                    :> ("one2one"
                                        :> (QualifiedCapture "usr" UserId
                                            :> MultiVerb
                                                 'GET
                                                 '[JSON]
                                                 '[Respond
                                                     200
                                                     "MLS 1-1 conversation"
                                                     (MLSOne2OneConversation MLSPublicKey)]
                                                 (MLSOne2OneConversation MLSPublicKey)))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Qualified UserId
-> Sem
     '[Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'NotConnected ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (MLSOne2OneConversation MLSPublicKey)
forall (r :: EffectRow).
(Member BrigAccess r, Member ConversationStore r,
 Member (Input Env) r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member FederatorAccess r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified UserId -> Sem r (MLSOne2OneConversation MLSPublicKey)
getMLSOne2OneConversationV6
    API
  (Named
     "get-one-to-one-mls-conversation@v6"
     (Summary "Get an MLS 1:1 conversation"
      :> (From 'V6
          :> (Until 'V7
              :> (ZLocalUser
                  :> (CanThrow 'MLSNotEnabled
                      :> (CanThrow 'NotConnected
                          :> ("conversations"
                              :> ("one2one"
                                  :> (QualifiedCapture "usr" UserId
                                      :> MultiVerb
                                           'GET
                                           '[JSON]
                                           '[Respond
                                               200
                                               "MLS 1-1 conversation"
                                               (MLSOne2OneConversation MLSPublicKey)]
                                           (MLSOne2OneConversation MLSPublicKey)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V7
             :> (ZLocalUser
                 :> (CanThrow 'MLSNotEnabled
                     :> (CanThrow 'NotConnected
                         :> ("conversations"
                             :> ("one2one"
                                 :> (QualifiedCapture "usr" UserId
                                     :> (QueryParam "format" MLSPublicKeyFormat
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200
                                                  "MLS 1-1 conversation"
                                                  (MLSOne2OneConversation SomeKey)]
                                              (MLSOne2OneConversation SomeKey))))))))))
      :<|> (Named
              "add-members-to-conversation-unqualified"
              (Summary "Add members to an existing conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (Until 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 Invite
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    ConvUpdateResponses
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))))))))
            :<|> (Named
                    "add-members-to-conversation-unqualified2"
                    (Summary "Add qualified members to an existing conversation."
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (Until 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> ("v2"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           InviteQualified
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvUpdateResponses
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))))))))
                  :<|> (Named
                          "add-members-to-conversation"
                          (Summary "Add qualified members to an existing conversation."
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (From 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             InviteQualified
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                ConvUpdateResponses
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))))))))
                        :<|> (Named
                                "join-conversation-by-id-unqualified"
                                (Summary
                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                 :> (Until 'V5
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TooManyMembers
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("join"
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      ConvJoinResponses
                                                                                      (UpdateResult
                                                                                         Event))))))))))))))
                              :<|> (Named
                                      "join-conversation-by-code-unqualified"
                                      (Summary "Join a conversation using a reusable code"
                                       :> (Description
                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (CanThrow 'CodeNotFound
                                                   :> (CanThrow 'InvalidConversationPassword
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'GuestLinksDisabled
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TooManyMembers
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> ("join"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     JoinConversationByCode
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvJoinResponses
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))
                                    :<|> (Named
                                            "code-check"
                                            (Summary "Check validity of a conversation code."
                                             :> (Description
                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                 :> (CanThrow 'CodeNotFound
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidConversationPassword
                                                             :> ("conversations"
                                                                 :> ("code-check"
                                                                     :> (ReqBody
                                                                           '[JSON] ConversationCode
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200 "Valid"]
                                                                              ()))))))))
                                          :<|> (Named
                                                  "create-conversation-code-unqualified@v3"
                                                  (Summary "Create or recreate a conversation code"
                                                   :> (Until 'V4
                                                       :> (DescriptionOAuthScope
                                                             'WriteConversationsCode
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow
                                                                             'CreateConversationCodeConflict
                                                                           :> (ZUser
                                                                               :> (ZHostOpt
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                :<|> (Named
                                                        "create-conversation-code-unqualified"
                                                        (Summary
                                                           "Create or recreate a conversation code"
                                                         :> (From 'V4
                                                             :> (DescriptionOAuthScope
                                                                   'WriteConversationsCode
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'CreateConversationCodeConflict
                                                                                 :> (ZUser
                                                                                     :> (ZHostOpt
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               CreateConversationCodeRequest
                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                      :<|> (Named
                                                              "get-conversation-guest-links-status"
                                                              (Summary
                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZUser
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("features"
                                                                                       :> ("conversationGuestLinks"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   GuestLinksConfig)))))))))
                                                            :<|> (Named
                                                                    "remove-code-unqualified"
                                                                    (Summary
                                                                       "Delete conversation code"
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("code"
                                                                                                 :> MultiVerb
                                                                                                      'DELETE
                                                                                                      '[JSON]
                                                                                                      '[Respond
                                                                                                          200
                                                                                                          "Conversation code deleted."
                                                                                                          Event]
                                                                                                      Event))))))))
                                                                  :<|> (Named
                                                                          "get-code"
                                                                          (Summary
                                                                             "Get existing conversation code"
                                                                           :> (CanThrow
                                                                                 'CodeNotFound
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'GuestLinksDisabled
                                                                                           :> (ZHostOpt
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[Respond
                                                                                                                        200
                                                                                                                        "Conversation Code"
                                                                                                                        ConversationCodeInfo]
                                                                                                                    ConversationCodeInfo))))))))))
                                                                        :<|> (Named
                                                                                "member-typing-unqualified"
                                                                                (Summary
                                                                                   "Sending typing notifications"
                                                                                 :> (Until 'V3
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "update-typing-indicator"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-typing-indicator-updated"
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("typing"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           TypingStatus
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Notification sent"]
                                                                                                                              ())))))))))))
                                                                              :<|> (Named
                                                                                      "member-typing-qualified"
                                                                                      (Summary
                                                                                         "Sending typing notifications"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "update-typing-indicator"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-typing-indicator-updated"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("typing"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             TypingStatus
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "Notification sent"]
                                                                                                                                ()))))))))))
                                                                                    :<|> (Named
                                                                                            "remove-member-unqualified"
                                                                                            (Summary
                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "leave-conversation"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (Until
                                                                                                                   'V2
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Target User ID"]
                                                                                                                                                       "usr"
                                                                                                                                                       UserId
                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-member"
                                                                                                  (Summary
                                                                                                     "Remove a member from a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "leave-conversation"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'RemoveConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("members"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Target User ID"]
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-other-member-unqualified"
                                                                                                        (Summary
                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvMemberNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidTarget
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("members"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                      200
                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-other-member"
                                                                                                              (Summary
                                                                                                                 "Update membership of the specified user"
                                                                                                               :> (Description
                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidTarget
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("members"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                             "usr"
                                                                                                                                                                             UserId
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                    ())))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationName)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationRename
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("name"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("name"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                         Event)
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                           Event)
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                            (Summary
                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "update-conversation"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "update-conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                        'V5
                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation@v6"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V6
             :> (Until 'V7
                 :> (ZLocalUser
                     :> (CanThrow 'MLSNotEnabled
                         :> (CanThrow 'NotConnected
                             :> ("conversations"
                                 :> ("one2one"
                                     :> (QualifiedCapture "usr" UserId
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200
                                                  "MLS 1-1 conversation"
                                                  (MLSOne2OneConversation MLSPublicKey)]
                                              (MLSOne2OneConversation MLSPublicKey))))))))))
      :<|> (Named
              "get-one-to-one-mls-conversation"
              (Summary "Get an MLS 1:1 conversation"
               :> (From 'V7
                   :> (ZLocalUser
                       :> (CanThrow 'MLSNotEnabled
                           :> (CanThrow 'NotConnected
                               :> ("conversations"
                                   :> ("one2one"
                                       :> (QualifiedCapture "usr" UserId
                                           :> (QueryParam "format" MLSPublicKeyFormat
                                               :> MultiVerb
                                                    'GET
                                                    '[JSON]
                                                    '[Respond
                                                        200
                                                        "MLS 1-1 conversation"
                                                        (MLSOne2OneConversation SomeKey)]
                                                    (MLSOne2OneConversation SomeKey))))))))))
            :<|> (Named
                    "add-members-to-conversation-unqualified"
                    (Summary "Add members to an existing conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (Until 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       Invite
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          ConvUpdateResponses
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))))))))
                  :<|> (Named
                          "add-members-to-conversation-unqualified2"
                          (Summary "Add qualified members to an existing conversation."
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (Until 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> ("v2"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 InviteQualified
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    ConvUpdateResponses
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))))))))
                        :<|> (Named
                                "add-members-to-conversation"
                                (Summary "Add qualified members to an existing conversation."
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (From 'V2
                                             :> (CanThrow ('ActionDenied 'AddConversationMember)
                                                 :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> (CanThrow 'TooManyMembers
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'NotConnected
                                                                             :> (CanThrow
                                                                                   'MissingLegalholdConsent
                                                                                 :> (CanThrow
                                                                                       NonFederatingBackends
                                                                                     :> (CanThrow
                                                                                           UnreachableBackends
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   InviteQualified
                                                                                                                 :> MultiVerb
                                                                                                                      'POST
                                                                                                                      '[JSON]
                                                                                                                      ConvUpdateResponses
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))))))))
                              :<|> (Named
                                      "join-conversation-by-id-unqualified"
                                      (Summary
                                         "Join a conversation by its ID (if link access enabled) (deprecated)"
                                       :> (Until 'V5
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TooManyMembers
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("join"
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            ConvJoinResponses
                                                                                            (UpdateResult
                                                                                               Event))))))))))))))
                                    :<|> (Named
                                            "join-conversation-by-code-unqualified"
                                            (Summary "Join a conversation using a reusable code"
                                             :> (Description
                                                   "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (CanThrow 'CodeNotFound
                                                         :> (CanThrow 'InvalidConversationPassword
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'GuestLinksDisabled
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'NotATeamMember
                                                                                 :> (CanThrow
                                                                                       'TooManyMembers
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> ("join"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           JoinConversationByCode
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvJoinResponses
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))
                                          :<|> (Named
                                                  "code-check"
                                                  (Summary "Check validity of a conversation code."
                                                   :> (Description
                                                         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                       :> (CanThrow 'CodeNotFound
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow
                                                                     'InvalidConversationPassword
                                                                   :> ("conversations"
                                                                       :> ("code-check"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationCode
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200 "Valid"]
                                                                                    ()))))))))
                                                :<|> (Named
                                                        "create-conversation-code-unqualified@v3"
                                                        (Summary
                                                           "Create or recreate a conversation code"
                                                         :> (Until 'V4
                                                             :> (DescriptionOAuthScope
                                                                   'WriteConversationsCode
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'CreateConversationCodeConflict
                                                                                 :> (ZUser
                                                                                     :> (ZHostOpt
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> CreateConversationCodeVerb)))))))))))))
                                                      :<|> (Named
                                                              "create-conversation-code-unqualified"
                                                              (Summary
                                                                 "Create or recreate a conversation code"
                                                               :> (From 'V4
                                                                   :> (DescriptionOAuthScope
                                                                         'WriteConversationsCode
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'GuestLinksDisabled
                                                                                   :> (CanThrow
                                                                                         'CreateConversationCodeConflict
                                                                                       :> (ZUser
                                                                                           :> (ZHostOpt
                                                                                               :> (ZOptConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     CreateConversationCodeRequest
                                                                                                                   :> CreateConversationCodeVerb))))))))))))))
                                                            :<|> (Named
                                                                    "get-conversation-guest-links-status"
                                                                    (Summary
                                                                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZUser
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("features"
                                                                                             :> ("conversationGuestLinks"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         GuestLinksConfig)))))))))
                                                                  :<|> (Named
                                                                          "remove-code-unqualified"
                                                                          (Summary
                                                                             "Delete conversation code"
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("code"
                                                                                                       :> MultiVerb
                                                                                                            'DELETE
                                                                                                            '[JSON]
                                                                                                            '[Respond
                                                                                                                200
                                                                                                                "Conversation code deleted."
                                                                                                                Event]
                                                                                                            Event))))))))
                                                                        :<|> (Named
                                                                                "get-code"
                                                                                (Summary
                                                                                   "Get existing conversation code"
                                                                                 :> (CanThrow
                                                                                       'CodeNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'GuestLinksDisabled
                                                                                                 :> (ZHostOpt
                                                                                                     :> (ZLocalUser
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("code"
                                                                                                                     :> MultiVerb
                                                                                                                          'GET
                                                                                                                          '[JSON]
                                                                                                                          '[Respond
                                                                                                                              200
                                                                                                                              "Conversation Code"
                                                                                                                              ConversationCodeInfo]
                                                                                                                          ConversationCodeInfo))))))))))
                                                                              :<|> (Named
                                                                                      "member-typing-unqualified"
                                                                                      (Summary
                                                                                         "Sending typing notifications"
                                                                                       :> (Until 'V3
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "update-typing-indicator"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-typing-indicator-updated"
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("typing"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 TypingStatus
                                                                                                                               :> MultiVerb
                                                                                                                                    'POST
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Notification sent"]
                                                                                                                                    ())))))))))))
                                                                                    :<|> (Named
                                                                                            "member-typing-qualified"
                                                                                            (Summary
                                                                                               "Sending typing notifications"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "update-typing-indicator"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-typing-indicator-updated"
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("typing"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   TypingStatus
                                                                                                                                 :> MultiVerb
                                                                                                                                      'POST
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "Notification sent"]
                                                                                                                                      ()))))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-member-unqualified"
                                                                                                  (Summary
                                                                                                     "Remove a member from a conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "leave-conversation"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (Until
                                                                                                                         'V2
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("members"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Target User ID"]
                                                                                                                                                             "usr"
                                                                                                                                                             UserId
                                                                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "remove-member"
                                                                                                        (Summary
                                                                                                           "Remove a member from a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "leave-conversation"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'RemoveConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("members"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Target User ID"]
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-other-member-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update membership of the specified user (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvMemberNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidTarget
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("members"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                                 "usr"
                                                                                                                                                                                 UserId
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                            200
                                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                                        ()))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-other-member"
                                                                                                                    (Summary
                                                                                                                       "Update membership of the specified user"
                                                                                                                     :> (Description
                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-conversation-updated"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-mls-message-sent"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvMemberNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidTarget
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("members"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Target User ID"]
                                                                                                                                                                                   "usr"
                                                                                                                                                                                   UserId
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                              200
                                                                                                                                                                                              "Membership updated"]
                                                                                                                                                                                          ())))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name-deprecated"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationRename
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                                       "Name updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationName)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("name"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationRename
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-name"
                                                                                                                                      (Summary
                                                                                                                                         "Update conversation name"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationName)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("name"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConversationRename
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                               "Name updated"
                                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                                               Event)
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-message-timer-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Brig
                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                 Event)))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-message-timer"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update the message timer for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "update-conversation"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-receipt-mode"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update receipt mode for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Galley
                                                                                                                                                                             "update-conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Brig
                                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access@v2"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-access"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                                       'Galley
                                                                                                                                                                                       "on-conversation-updated"
                                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                                           'Galley
                                                                                                                                                                                           "on-mls-message-sent"
                                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                                               'Brig
                                                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                                                             :> (From
                                                                                                                                                                                                   'V3
                                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (Maybe
                                                                                                                                                                                                                   Member)))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                                                                             :> (Deprecated
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                                          200
                                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                                      ()))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  "update-conversation-self"
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "Update self membership properties"
                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                                                            200
                                                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                                                        ())))))))))
                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                                                                        :> (From
                                                                                                                                                                                                              'V5
                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-one-to-one-mls-conversation" ServerT
  (Summary "Get an MLS 1:1 conversation"
   :> (From 'V7
       :> (ZLocalUser
           :> (CanThrow 'MLSNotEnabled
               :> (CanThrow 'NotConnected
                   :> ("conversations"
                       :> ("one2one"
                           :> (QualifiedCapture "usr" UserId
                               :> (QueryParam "format" MLSPublicKeyFormat
                                   :> MultiVerb
                                        'GET
                                        '[JSON]
                                        '[Respond
                                            200
                                            "MLS 1-1 conversation"
                                            (MLSOne2OneConversation SomeKey)]
                                        (MLSOne2OneConversation SomeKey))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get an MLS 1:1 conversation"
            :> (From 'V7
                :> (ZLocalUser
                    :> (CanThrow 'MLSNotEnabled
                        :> (CanThrow 'NotConnected
                            :> ("conversations"
                                :> ("one2one"
                                    :> (QualifiedCapture "usr" UserId
                                        :> (QueryParam "format" MLSPublicKeyFormat
                                            :> MultiVerb
                                                 'GET
                                                 '[JSON]
                                                 '[Respond
                                                     200
                                                     "MLS 1-1 conversation"
                                                     (MLSOne2OneConversation SomeKey)]
                                                 (MLSOne2OneConversation SomeKey)))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> Qualified UserId
-> Maybe MLSPublicKeyFormat
-> Sem
     '[Error (Tagged 'MLSNotEnabled ()),
       Error (Tagged 'NotConnected ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (MLSOne2OneConversation SomeKey)
forall (r :: EffectRow).
(Member BrigAccess r, Member ConversationStore r,
 Member (Input Env) r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member (Error (Tagged 'MLSNotEnabled ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member FederatorAccess r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> Qualified UserId
-> Maybe MLSPublicKeyFormat
-> Sem r (MLSOne2OneConversation SomeKey)
getMLSOne2OneConversation
    API
  (Named
     "get-one-to-one-mls-conversation"
     (Summary "Get an MLS 1:1 conversation"
      :> (From 'V7
          :> (ZLocalUser
              :> (CanThrow 'MLSNotEnabled
                  :> (CanThrow 'NotConnected
                      :> ("conversations"
                          :> ("one2one"
                              :> (QualifiedCapture "usr" UserId
                                  :> (QueryParam "format" MLSPublicKeyFormat
                                      :> MultiVerb
                                           'GET
                                           '[JSON]
                                           '[Respond
                                               200
                                               "MLS 1-1 conversation"
                                               (MLSOne2OneConversation SomeKey)]
                                           (MLSOne2OneConversation SomeKey)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "add-members-to-conversation-unqualified"
        (Summary "Add members to an existing conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (Until 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           Invite
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              ConvUpdateResponses
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))))))))
      :<|> (Named
              "add-members-to-conversation-unqualified2"
              (Summary "Add qualified members to an existing conversation."
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (Until 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> ("v2"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     InviteQualified
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvUpdateResponses
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))))))))
            :<|> (Named
                    "add-members-to-conversation"
                    (Summary "Add qualified members to an existing conversation."
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (From 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       InviteQualified
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          ConvUpdateResponses
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))))))))
                  :<|> (Named
                          "join-conversation-by-id-unqualified"
                          (Summary
                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                           :> (Until 'V5
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TooManyMembers
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("join"
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                ConvJoinResponses
                                                                                (UpdateResult
                                                                                   Event))))))))))))))
                        :<|> (Named
                                "join-conversation-by-code-unqualified"
                                (Summary "Join a conversation using a reusable code"
                                 :> (Description
                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (CanThrow 'CodeNotFound
                                             :> (CanThrow 'InvalidConversationPassword
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'GuestLinksDisabled
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TooManyMembers
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> ("join"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               JoinConversationByCode
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvJoinResponses
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))
                              :<|> (Named
                                      "code-check"
                                      (Summary "Check validity of a conversation code."
                                       :> (Description
                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                           :> (CanThrow 'CodeNotFound
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidConversationPassword
                                                       :> ("conversations"
                                                           :> ("code-check"
                                                               :> (ReqBody '[JSON] ConversationCode
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty 200 "Valid"]
                                                                        ()))))))))
                                    :<|> (Named
                                            "create-conversation-code-unqualified@v3"
                                            (Summary "Create or recreate a conversation code"
                                             :> (Until 'V4
                                                 :> (DescriptionOAuthScope 'WriteConversationsCode
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow
                                                                       'CreateConversationCodeConflict
                                                                     :> (ZUser
                                                                         :> (ZHostOpt
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                          :<|> (Named
                                                  "create-conversation-code-unqualified"
                                                  (Summary "Create or recreate a conversation code"
                                                   :> (From 'V4
                                                       :> (DescriptionOAuthScope
                                                             'WriteConversationsCode
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow
                                                                             'CreateConversationCodeConflict
                                                                           :> (ZUser
                                                                               :> (ZHostOpt
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         CreateConversationCodeRequest
                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                :<|> (Named
                                                        "get-conversation-guest-links-status"
                                                        (Summary
                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZUser
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("features"
                                                                                 :> ("conversationGuestLinks"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             GuestLinksConfig)))))))))
                                                      :<|> (Named
                                                              "remove-code-unqualified"
                                                              (Summary "Delete conversation code"
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("code"
                                                                                           :> MultiVerb
                                                                                                'DELETE
                                                                                                '[JSON]
                                                                                                '[Respond
                                                                                                    200
                                                                                                    "Conversation code deleted."
                                                                                                    Event]
                                                                                                Event))))))))
                                                            :<|> (Named
                                                                    "get-code"
                                                                    (Summary
                                                                       "Get existing conversation code"
                                                                     :> (CanThrow 'CodeNotFound
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'GuestLinksDisabled
                                                                                     :> (ZHostOpt
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[Respond
                                                                                                                  200
                                                                                                                  "Conversation Code"
                                                                                                                  ConversationCodeInfo]
                                                                                                              ConversationCodeInfo))))))))))
                                                                  :<|> (Named
                                                                          "member-typing-unqualified"
                                                                          (Summary
                                                                             "Sending typing notifications"
                                                                           :> (Until 'V3
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "update-typing-indicator"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-typing-indicator-updated"
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("typing"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     TypingStatus
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Notification sent"]
                                                                                                                        ())))))))))))
                                                                        :<|> (Named
                                                                                "member-typing-qualified"
                                                                                (Summary
                                                                                   "Sending typing notifications"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "update-typing-indicator"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-typing-indicator-updated"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("typing"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       TypingStatus
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "Notification sent"]
                                                                                                                          ()))))))))))
                                                                              :<|> (Named
                                                                                      "remove-member-unqualified"
                                                                                      (Summary
                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "leave-conversation"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (Until
                                                                                                             'V2
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Target User ID"]
                                                                                                                                                 "usr"
                                                                                                                                                 UserId
                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "remove-member"
                                                                                            (Summary
                                                                                               "Remove a member from a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "leave-conversation"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'RemoveConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("members"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Target User ID"]
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-other-member-unqualified"
                                                                                                  (Summary
                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvMemberNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidTarget
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("members"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                200
                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                            ()))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-other-member"
                                                                                                        (Summary
                                                                                                           "Update membership of the specified user"
                                                                                                         :> (Description
                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvMemberNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidTarget
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("members"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                       "usr"
                                                                                                                                                                       UserId
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                              ())))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name-deprecated"
                                                                                                              (Summary
                                                                                                                 "Update conversation name (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationName)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationRename
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                           "Name updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationName)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("name"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationRename
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationName)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("name"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConversationRename
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                   Event)
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                     Event)
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                      (Summary
                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "update-conversation"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "update-conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                           (Summary
                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                            :> (From
                                                                                                                                                                                                  'V5
                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-one-to-one-mls-conversation"
        (Summary "Get an MLS 1:1 conversation"
         :> (From 'V7
             :> (ZLocalUser
                 :> (CanThrow 'MLSNotEnabled
                     :> (CanThrow 'NotConnected
                         :> ("conversations"
                             :> ("one2one"
                                 :> (QualifiedCapture "usr" UserId
                                     :> (QueryParam "format" MLSPublicKeyFormat
                                         :> MultiVerb
                                              'GET
                                              '[JSON]
                                              '[Respond
                                                  200
                                                  "MLS 1-1 conversation"
                                                  (MLSOne2OneConversation SomeKey)]
                                              (MLSOne2OneConversation SomeKey))))))))))
      :<|> (Named
              "add-members-to-conversation-unqualified"
              (Summary "Add members to an existing conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (Until 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 Invite
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    ConvUpdateResponses
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))))))))
            :<|> (Named
                    "add-members-to-conversation-unqualified2"
                    (Summary "Add qualified members to an existing conversation."
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (Until 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> ("v2"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           InviteQualified
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              ConvUpdateResponses
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))))))))
                  :<|> (Named
                          "add-members-to-conversation"
                          (Summary "Add qualified members to an existing conversation."
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (From 'V2
                                       :> (CanThrow ('ActionDenied 'AddConversationMember)
                                           :> (CanThrow ('ActionDenied 'LeaveConversation)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> (CanThrow 'TooManyMembers
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'NotConnected
                                                                       :> (CanThrow
                                                                             'MissingLegalholdConsent
                                                                           :> (CanThrow
                                                                                 NonFederatingBackends
                                                                               :> (CanThrow
                                                                                     UnreachableBackends
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             InviteQualified
                                                                                                           :> MultiVerb
                                                                                                                'POST
                                                                                                                '[JSON]
                                                                                                                ConvUpdateResponses
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))))))))
                        :<|> (Named
                                "join-conversation-by-id-unqualified"
                                (Summary
                                   "Join a conversation by its ID (if link access enabled) (deprecated)"
                                 :> (Until 'V5
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TooManyMembers
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("join"
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      ConvJoinResponses
                                                                                      (UpdateResult
                                                                                         Event))))))))))))))
                              :<|> (Named
                                      "join-conversation-by-code-unqualified"
                                      (Summary "Join a conversation using a reusable code"
                                       :> (Description
                                             "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (CanThrow 'CodeNotFound
                                                   :> (CanThrow 'InvalidConversationPassword
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'GuestLinksDisabled
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow 'NotATeamMember
                                                                           :> (CanThrow
                                                                                 'TooManyMembers
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> ("join"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     JoinConversationByCode
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvJoinResponses
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))
                                    :<|> (Named
                                            "code-check"
                                            (Summary "Check validity of a conversation code."
                                             :> (Description
                                                   "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                                 :> (CanThrow 'CodeNotFound
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidConversationPassword
                                                             :> ("conversations"
                                                                 :> ("code-check"
                                                                     :> (ReqBody
                                                                           '[JSON] ConversationCode
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200 "Valid"]
                                                                              ()))))))))
                                          :<|> (Named
                                                  "create-conversation-code-unqualified@v3"
                                                  (Summary "Create or recreate a conversation code"
                                                   :> (Until 'V4
                                                       :> (DescriptionOAuthScope
                                                             'WriteConversationsCode
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow
                                                                             'CreateConversationCodeConflict
                                                                           :> (ZUser
                                                                               :> (ZHostOpt
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> CreateConversationCodeVerb)))))))))))))
                                                :<|> (Named
                                                        "create-conversation-code-unqualified"
                                                        (Summary
                                                           "Create or recreate a conversation code"
                                                         :> (From 'V4
                                                             :> (DescriptionOAuthScope
                                                                   'WriteConversationsCode
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'GuestLinksDisabled
                                                                             :> (CanThrow
                                                                                   'CreateConversationCodeConflict
                                                                                 :> (ZUser
                                                                                     :> (ZHostOpt
                                                                                         :> (ZOptConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               CreateConversationCodeRequest
                                                                                                             :> CreateConversationCodeVerb))))))))))))))
                                                      :<|> (Named
                                                              "get-conversation-guest-links-status"
                                                              (Summary
                                                                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZUser
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("features"
                                                                                       :> ("conversationGuestLinks"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   GuestLinksConfig)))))))))
                                                            :<|> (Named
                                                                    "remove-code-unqualified"
                                                                    (Summary
                                                                       "Delete conversation code"
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("code"
                                                                                                 :> MultiVerb
                                                                                                      'DELETE
                                                                                                      '[JSON]
                                                                                                      '[Respond
                                                                                                          200
                                                                                                          "Conversation code deleted."
                                                                                                          Event]
                                                                                                      Event))))))))
                                                                  :<|> (Named
                                                                          "get-code"
                                                                          (Summary
                                                                             "Get existing conversation code"
                                                                           :> (CanThrow
                                                                                 'CodeNotFound
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'GuestLinksDisabled
                                                                                           :> (ZHostOpt
                                                                                               :> (ZLocalUser
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("code"
                                                                                                               :> MultiVerb
                                                                                                                    'GET
                                                                                                                    '[JSON]
                                                                                                                    '[Respond
                                                                                                                        200
                                                                                                                        "Conversation Code"
                                                                                                                        ConversationCodeInfo]
                                                                                                                    ConversationCodeInfo))))))))))
                                                                        :<|> (Named
                                                                                "member-typing-unqualified"
                                                                                (Summary
                                                                                   "Sending typing notifications"
                                                                                 :> (Until 'V3
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "update-typing-indicator"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-typing-indicator-updated"
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("typing"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           TypingStatus
                                                                                                                         :> MultiVerb
                                                                                                                              'POST
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Notification sent"]
                                                                                                                              ())))))))))))
                                                                              :<|> (Named
                                                                                      "member-typing-qualified"
                                                                                      (Summary
                                                                                         "Sending typing notifications"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "update-typing-indicator"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-typing-indicator-updated"
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("typing"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             TypingStatus
                                                                                                                           :> MultiVerb
                                                                                                                                'POST
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "Notification sent"]
                                                                                                                                ()))))))))))
                                                                                    :<|> (Named
                                                                                            "remove-member-unqualified"
                                                                                            (Summary
                                                                                               "Remove a member from a conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "leave-conversation"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (Until
                                                                                                                   'V2
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("members"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Target User ID"]
                                                                                                                                                       "usr"
                                                                                                                                                       UserId
                                                                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "remove-member"
                                                                                                  (Summary
                                                                                                     "Remove a member from a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "leave-conversation"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'RemoveConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("members"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Target User ID"]
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-other-member-unqualified"
                                                                                                        (Summary
                                                                                                           "Update membership of the specified user (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvMemberNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidTarget
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("members"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Target User ID"]
                                                                                                                                                                           "usr"
                                                                                                                                                                           UserId
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                      200
                                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                                  ()))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-other-member"
                                                                                                              (Summary
                                                                                                                 "Update membership of the specified user"
                                                                                                               :> (Description
                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-conversation-updated"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-mls-message-sent"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvMemberNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidTarget
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("members"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Target User ID"]
                                                                                                                                                                             "usr"
                                                                                                                                                                             UserId
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 OtherMemberUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                        200
                                                                                                                                                                                        "Membership updated"]
                                                                                                                                                                                    ())))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name-deprecated"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationName)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationRename
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                                 "Name updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationName)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("name"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationRename
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                                           "Name updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-name"
                                                                                                                                (Summary
                                                                                                                                   "Update conversation name"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationName)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("name"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConversationRename
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                         "Name updated"
                                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                                         Event)
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-message-timer-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Brig
                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("message-timer"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                                                           Event)
                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                           Event)))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-message-timer"
                                                                                                                                            (Summary
                                                                                                                                               "Update the message timer for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "update-conversation"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-receipt-mode"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update receipt mode for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Galley
                                                                                                                                                                       "update-conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Brig
                                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access@v2"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-access"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update access modes for a conversation"
                                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                                 'Galley
                                                                                                                                                                                 "on-conversation-updated"
                                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                                     'Galley
                                                                                                                                                                                     "on-mls-message-sent"
                                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                                         'Brig
                                                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                                                       :> (From
                                                                                                                                                                                             'V3
                                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (Maybe
                                                                                                                                                                                                             Member)))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                                                                       :> (Deprecated
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                                    200
                                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                                ()))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            "update-conversation-self"
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "Update self membership properties"
                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                                                      200
                                                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                                                  ())))))))))
                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                                                                  :> (From
                                                                                                                                                                                                        'V5
                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'ConvNotFound
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"add-members-to-conversation-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> Invite
 -> Sem
      '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
        Error (Tagged ('ActionDenied 'LeaveConversation) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'TooManyMembers ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Invite
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-updated",
 (HasAnnotation 'Remote "galley" "on-mls-message-sent",
  () :: Constraint)) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Invite
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Invite
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'AddConversationMember) ())) r,
 Member (Error (Tagged ('ActionDenied 'LeaveConversation) ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error NonFederatingBackends) r,
 Member (Error UnreachableBackends) r, Member ExternalAccess r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member MemberStore r, Member ProposalStore r, Member Random r,
 Member SubConversationStore r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> Invite -> Sem r (UpdateResult Event)
addMembersUnqualified)
    API
  (Named
     "add-members-to-conversation-unqualified"
     (Summary "Add members to an existing conversation (deprecated)"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (Until 'V2
                  :> (CanThrow ('ActionDenied 'AddConversationMember)
                      :> (CanThrow ('ActionDenied 'LeaveConversation)
                          :> (CanThrow 'ConvNotFound
                              :> (CanThrow 'InvalidOperation
                                  :> (CanThrow 'TooManyMembers
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'NotConnected
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow NonFederatingBackends
                                                          :> (CanThrow UnreachableBackends
                                                              :> (ZLocalUser
                                                                  :> (ZConn
                                                                      :> ("conversations"
                                                                          :> (Capture "cnv" ConvId
                                                                              :> ("members"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        Invite
                                                                                      :> MultiVerb
                                                                                           'POST
                                                                                           '[JSON]
                                                                                           ConvUpdateResponses
                                                                                           (UpdateResult
                                                                                              Event)))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "add-members-to-conversation-unqualified2"
        (Summary "Add qualified members to an existing conversation."
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (Until 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> ("v2"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               InviteQualified
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvUpdateResponses
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))))))))
      :<|> (Named
              "add-members-to-conversation"
              (Summary "Add qualified members to an existing conversation."
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (From 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 InviteQualified
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    ConvUpdateResponses
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))))))))
            :<|> (Named
                    "join-conversation-by-id-unqualified"
                    (Summary
                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                     :> (Until 'V5
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TooManyMembers
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("join"
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          ConvJoinResponses
                                                                          (UpdateResult
                                                                             Event))))))))))))))
                  :<|> (Named
                          "join-conversation-by-code-unqualified"
                          (Summary "Join a conversation using a reusable code"
                           :> (Description
                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (CanThrow 'CodeNotFound
                                       :> (CanThrow 'InvalidConversationPassword
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'GuestLinksDisabled
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TooManyMembers
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> ("join"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         JoinConversationByCode
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            ConvJoinResponses
                                                                                            (UpdateResult
                                                                                               Event)))))))))))))))))
                        :<|> (Named
                                "code-check"
                                (Summary "Check validity of a conversation code."
                                 :> (Description
                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                     :> (CanThrow 'CodeNotFound
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidConversationPassword
                                                 :> ("conversations"
                                                     :> ("code-check"
                                                         :> (ReqBody '[JSON] ConversationCode
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty 200 "Valid"]
                                                                  ()))))))))
                              :<|> (Named
                                      "create-conversation-code-unqualified@v3"
                                      (Summary "Create or recreate a conversation code"
                                       :> (Until 'V4
                                           :> (DescriptionOAuthScope 'WriteConversationsCode
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow
                                                                 'CreateConversationCodeConflict
                                                               :> (ZUser
                                                                   :> (ZHostOpt
                                                                       :> (ZOptConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                    :<|> (Named
                                            "create-conversation-code-unqualified"
                                            (Summary "Create or recreate a conversation code"
                                             :> (From 'V4
                                                 :> (DescriptionOAuthScope 'WriteConversationsCode
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow
                                                                       'CreateConversationCodeConflict
                                                                     :> (ZUser
                                                                         :> (ZHostOpt
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   CreateConversationCodeRequest
                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                          :<|> (Named
                                                  "get-conversation-guest-links-status"
                                                  (Summary
                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZUser
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("features"
                                                                           :> ("conversationGuestLinks"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       GuestLinksConfig)))))))))
                                                :<|> (Named
                                                        "remove-code-unqualified"
                                                        (Summary "Delete conversation code"
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("code"
                                                                                     :> MultiVerb
                                                                                          'DELETE
                                                                                          '[JSON]
                                                                                          '[Respond
                                                                                              200
                                                                                              "Conversation code deleted."
                                                                                              Event]
                                                                                          Event))))))))
                                                      :<|> (Named
                                                              "get-code"
                                                              (Summary
                                                                 "Get existing conversation code"
                                                               :> (CanThrow 'CodeNotFound
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'GuestLinksDisabled
                                                                               :> (ZHostOpt
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[Respond
                                                                                                            200
                                                                                                            "Conversation Code"
                                                                                                            ConversationCodeInfo]
                                                                                                        ConversationCodeInfo))))))))))
                                                            :<|> (Named
                                                                    "member-typing-unqualified"
                                                                    (Summary
                                                                       "Sending typing notifications"
                                                                     :> (Until 'V3
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "update-typing-indicator"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-typing-indicator-updated"
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("typing"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               TypingStatus
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Notification sent"]
                                                                                                                  ())))))))))))
                                                                  :<|> (Named
                                                                          "member-typing-qualified"
                                                                          (Summary
                                                                             "Sending typing notifications"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "update-typing-indicator"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-typing-indicator-updated"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("typing"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 TypingStatus
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "Notification sent"]
                                                                                                                    ()))))))))))
                                                                        :<|> (Named
                                                                                "remove-member-unqualified"
                                                                                (Summary
                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "leave-conversation"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (Until
                                                                                                       'V2
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Target User ID"]
                                                                                                                                           "usr"
                                                                                                                                           UserId
                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                              :<|> (Named
                                                                                      "remove-member"
                                                                                      (Summary
                                                                                         "Remove a member from a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "leave-conversation"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'RemoveConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("members"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Target User ID"]
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-other-member-unqualified"
                                                                                            (Summary
                                                                                               "Update membership of the specified user (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvMemberNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidTarget
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("members"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Target User ID"]
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                          200
                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                      ()))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-other-member"
                                                                                                  (Summary
                                                                                                     "Update membership of the specified user"
                                                                                                   :> (Description
                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvMemberNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidTarget
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("members"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                 "usr"
                                                                                                                                                                 UserId
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                        ())))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name-deprecated"
                                                                                                        (Summary
                                                                                                           "Update conversation name (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationName)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationRename
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                     "Name updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update conversation name (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationName)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("name"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationRename
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                               "Name updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationName)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("name"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConversationRename
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                             "Name updated"
                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                             Event)
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                               Event)
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-message-timer"
                                                                                                                                (Summary
                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "update-conversation"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                            (Summary
                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "update-conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                              :<|> Named
                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                     (Summary
                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                      :> (From
                                                                                                                                                                                            'V5
                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "add-members-to-conversation-unqualified"
        (Summary "Add members to an existing conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (Until 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           Invite
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              ConvUpdateResponses
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))))))))
      :<|> (Named
              "add-members-to-conversation-unqualified2"
              (Summary "Add qualified members to an existing conversation."
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (Until 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> ("v2"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     InviteQualified
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        ConvUpdateResponses
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))))))))
            :<|> (Named
                    "add-members-to-conversation"
                    (Summary "Add qualified members to an existing conversation."
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (From 'V2
                                 :> (CanThrow ('ActionDenied 'AddConversationMember)
                                     :> (CanThrow ('ActionDenied 'LeaveConversation)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> (CanThrow 'TooManyMembers
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'NotConnected
                                                                 :> (CanThrow
                                                                       'MissingLegalholdConsent
                                                                     :> (CanThrow
                                                                           NonFederatingBackends
                                                                         :> (CanThrow
                                                                               UnreachableBackends
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       InviteQualified
                                                                                                     :> MultiVerb
                                                                                                          'POST
                                                                                                          '[JSON]
                                                                                                          ConvUpdateResponses
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))))))))
                  :<|> (Named
                          "join-conversation-by-id-unqualified"
                          (Summary
                             "Join a conversation by its ID (if link access enabled) (deprecated)"
                           :> (Until 'V5
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TooManyMembers
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("join"
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                ConvJoinResponses
                                                                                (UpdateResult
                                                                                   Event))))))))))))))
                        :<|> (Named
                                "join-conversation-by-code-unqualified"
                                (Summary "Join a conversation using a reusable code"
                                 :> (Description
                                       "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (CanThrow 'CodeNotFound
                                             :> (CanThrow 'InvalidConversationPassword
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'GuestLinksDisabled
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'NotATeamMember
                                                                     :> (CanThrow 'TooManyMembers
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> ("join"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               JoinConversationByCode
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvJoinResponses
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))
                              :<|> (Named
                                      "code-check"
                                      (Summary "Check validity of a conversation code."
                                       :> (Description
                                             "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                           :> (CanThrow 'CodeNotFound
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidConversationPassword
                                                       :> ("conversations"
                                                           :> ("code-check"
                                                               :> (ReqBody '[JSON] ConversationCode
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty 200 "Valid"]
                                                                        ()))))))))
                                    :<|> (Named
                                            "create-conversation-code-unqualified@v3"
                                            (Summary "Create or recreate a conversation code"
                                             :> (Until 'V4
                                                 :> (DescriptionOAuthScope 'WriteConversationsCode
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow
                                                                       'CreateConversationCodeConflict
                                                                     :> (ZUser
                                                                         :> (ZHostOpt
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> CreateConversationCodeVerb)))))))))))))
                                          :<|> (Named
                                                  "create-conversation-code-unqualified"
                                                  (Summary "Create or recreate a conversation code"
                                                   :> (From 'V4
                                                       :> (DescriptionOAuthScope
                                                             'WriteConversationsCode
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'GuestLinksDisabled
                                                                       :> (CanThrow
                                                                             'CreateConversationCodeConflict
                                                                           :> (ZUser
                                                                               :> (ZHostOpt
                                                                                   :> (ZOptConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         CreateConversationCodeRequest
                                                                                                       :> CreateConversationCodeVerb))))))))))))))
                                                :<|> (Named
                                                        "get-conversation-guest-links-status"
                                                        (Summary
                                                           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZUser
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("features"
                                                                                 :> ("conversationGuestLinks"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             GuestLinksConfig)))))))))
                                                      :<|> (Named
                                                              "remove-code-unqualified"
                                                              (Summary "Delete conversation code"
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("code"
                                                                                           :> MultiVerb
                                                                                                'DELETE
                                                                                                '[JSON]
                                                                                                '[Respond
                                                                                                    200
                                                                                                    "Conversation code deleted."
                                                                                                    Event]
                                                                                                Event))))))))
                                                            :<|> (Named
                                                                    "get-code"
                                                                    (Summary
                                                                       "Get existing conversation code"
                                                                     :> (CanThrow 'CodeNotFound
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'GuestLinksDisabled
                                                                                     :> (ZHostOpt
                                                                                         :> (ZLocalUser
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("code"
                                                                                                         :> MultiVerb
                                                                                                              'GET
                                                                                                              '[JSON]
                                                                                                              '[Respond
                                                                                                                  200
                                                                                                                  "Conversation Code"
                                                                                                                  ConversationCodeInfo]
                                                                                                              ConversationCodeInfo))))))))))
                                                                  :<|> (Named
                                                                          "member-typing-unqualified"
                                                                          (Summary
                                                                             "Sending typing notifications"
                                                                           :> (Until 'V3
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "update-typing-indicator"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-typing-indicator-updated"
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("typing"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     TypingStatus
                                                                                                                   :> MultiVerb
                                                                                                                        'POST
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Notification sent"]
                                                                                                                        ())))))))))))
                                                                        :<|> (Named
                                                                                "member-typing-qualified"
                                                                                (Summary
                                                                                   "Sending typing notifications"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "update-typing-indicator"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-typing-indicator-updated"
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("typing"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       TypingStatus
                                                                                                                     :> MultiVerb
                                                                                                                          'POST
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "Notification sent"]
                                                                                                                          ()))))))))))
                                                                              :<|> (Named
                                                                                      "remove-member-unqualified"
                                                                                      (Summary
                                                                                         "Remove a member from a conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "leave-conversation"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (Until
                                                                                                             'V2
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("members"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Target User ID"]
                                                                                                                                                 "usr"
                                                                                                                                                 UserId
                                                                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "remove-member"
                                                                                            (Summary
                                                                                               "Remove a member from a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "leave-conversation"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'RemoveConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("members"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Target User ID"]
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-other-member-unqualified"
                                                                                                  (Summary
                                                                                                     "Update membership of the specified user (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvMemberNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidTarget
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("members"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Target User ID"]
                                                                                                                                                                     "usr"
                                                                                                                                                                     UserId
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                200
                                                                                                                                                                                "Membership updated"]
                                                                                                                                                                            ()))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-other-member"
                                                                                                        (Summary
                                                                                                           "Update membership of the specified user"
                                                                                                         :> (Description
                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-conversation-updated"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-mls-message-sent"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvMemberNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyOtherConversationMember)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidTarget
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("members"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Target User ID"]
                                                                                                                                                                       "usr"
                                                                                                                                                                       UserId
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           OtherMemberUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                  200
                                                                                                                                                                                  "Membership updated"]
                                                                                                                                                                              ())))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name-deprecated"
                                                                                                              (Summary
                                                                                                                 "Update conversation name (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationName)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationRename
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Name unchanged"
                                                                                                                                                                           "Name updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationName)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("name"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationRename
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                                     "Name updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-name"
                                                                                                                          (Summary
                                                                                                                             "Update conversation name"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationName)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("name"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConversationRename
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                   "Name updated"
                                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                                   Event)
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-message-timer-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Brig
                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("message-timer"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                                                     Event)
                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                     Event)))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-message-timer"
                                                                                                                                      (Summary
                                                                                                                                         "Update the message timer for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "update-conversation"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-receipt-mode"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update receipt mode for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Galley
                                                                                                                                                                 "update-conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Brig
                                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                                               'V2
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access@v2"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-access"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update access modes for a conversation"
                                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                                           'Galley
                                                                                                                                                                           "on-conversation-updated"
                                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                                               'Galley
                                                                                                                                                                               "on-mls-message-sent"
                                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                                   'Brig
                                                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                                                 :> (From
                                                                                                                                                                                       'V3
                                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                                         :> (ZConn
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                                                             Event)
                                                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (Maybe
                                                                                                                                                                                                       Member)))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                                                                 :> (Deprecated
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                                               '[Description
                                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                                               "cnv"
                                                                                                                                                                                                               ConvId
                                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                                              200
                                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                                          ()))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      "update-conversation-self"
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "Update self membership properties"
                                                                                                                                                                                       :> (Description
                                                                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("self"
                                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                                                200
                                                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                                                            ())))))))))
                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                           "update-conversation-protocol"
                                                                                                                                                                                           (Summary
                                                                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                                                                            :> (From
                                                                                                                                                                                                  'V5
                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'ConvNotFound
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"add-members-to-conversation-unqualified2" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> InviteQualified
 -> Sem
      '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
        Error (Tagged ('ActionDenied 'LeaveConversation) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'TooManyMembers ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-updated",
 (HasAnnotation 'Remote "galley" "on-mls-message-sent",
  () :: Constraint)) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'AddConversationMember) ())) r,
 Member (Error (Tagged ('ActionDenied 'LeaveConversation) ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error NonFederatingBackends) r,
 Member (Error UnreachableBackends) r, Member ExternalAccess r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member MemberStore r, Member ProposalStore r, Member Random r,
 Member SubConversationStore r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> InviteQualified
-> Sem r (UpdateResult Event)
addMembersUnqualifiedV2)
    API
  (Named
     "add-members-to-conversation-unqualified2"
     (Summary "Add qualified members to an existing conversation."
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (Until 'V2
                  :> (CanThrow ('ActionDenied 'AddConversationMember)
                      :> (CanThrow ('ActionDenied 'LeaveConversation)
                          :> (CanThrow 'ConvNotFound
                              :> (CanThrow 'InvalidOperation
                                  :> (CanThrow 'TooManyMembers
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'NotConnected
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow NonFederatingBackends
                                                          :> (CanThrow UnreachableBackends
                                                              :> (ZLocalUser
                                                                  :> (ZConn
                                                                      :> ("conversations"
                                                                          :> (Capture "cnv" ConvId
                                                                              :> ("members"
                                                                                  :> ("v2"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            InviteQualified
                                                                                          :> MultiVerb
                                                                                               'POST
                                                                                               '[JSON]
                                                                                               ConvUpdateResponses
                                                                                               (UpdateResult
                                                                                                  Event))))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "add-members-to-conversation"
        (Summary "Add qualified members to an existing conversation."
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (From 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           InviteQualified
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              ConvUpdateResponses
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))))))))
      :<|> (Named
              "join-conversation-by-id-unqualified"
              (Summary
                 "Join a conversation by its ID (if link access enabled) (deprecated)"
               :> (Until 'V5
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TooManyMembers
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("join"
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    ConvJoinResponses
                                                                    (UpdateResult
                                                                       Event))))))))))))))
            :<|> (Named
                    "join-conversation-by-code-unqualified"
                    (Summary "Join a conversation using a reusable code"
                     :> (Description
                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (CanThrow 'CodeNotFound
                                 :> (CanThrow 'InvalidConversationPassword
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'GuestLinksDisabled
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TooManyMembers
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> ("join"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   JoinConversationByCode
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      ConvJoinResponses
                                                                                      (UpdateResult
                                                                                         Event)))))))))))))))))
                  :<|> (Named
                          "code-check"
                          (Summary "Check validity of a conversation code."
                           :> (Description
                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                               :> (CanThrow 'CodeNotFound
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidConversationPassword
                                           :> ("conversations"
                                               :> ("code-check"
                                                   :> (ReqBody '[JSON] ConversationCode
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty 200 "Valid"]
                                                            ()))))))))
                        :<|> (Named
                                "create-conversation-code-unqualified@v3"
                                (Summary "Create or recreate a conversation code"
                                 :> (Until 'V4
                                     :> (DescriptionOAuthScope 'WriteConversationsCode
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'CreateConversationCodeConflict
                                                         :> (ZUser
                                                             :> (ZHostOpt
                                                                 :> (ZOptConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> CreateConversationCodeVerb)))))))))))))
                              :<|> (Named
                                      "create-conversation-code-unqualified"
                                      (Summary "Create or recreate a conversation code"
                                       :> (From 'V4
                                           :> (DescriptionOAuthScope 'WriteConversationsCode
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow
                                                                 'CreateConversationCodeConflict
                                                               :> (ZUser
                                                                   :> (ZHostOpt
                                                                       :> (ZOptConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             CreateConversationCodeRequest
                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                    :<|> (Named
                                            "get-conversation-guest-links-status"
                                            (Summary
                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZUser
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("features"
                                                                     :> ("conversationGuestLinks"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 GuestLinksConfig)))))))))
                                          :<|> (Named
                                                  "remove-code-unqualified"
                                                  (Summary "Delete conversation code"
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("code"
                                                                               :> MultiVerb
                                                                                    'DELETE
                                                                                    '[JSON]
                                                                                    '[Respond
                                                                                        200
                                                                                        "Conversation code deleted."
                                                                                        Event]
                                                                                    Event))))))))
                                                :<|> (Named
                                                        "get-code"
                                                        (Summary "Get existing conversation code"
                                                         :> (CanThrow 'CodeNotFound
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'GuestLinksDisabled
                                                                         :> (ZHostOpt
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[Respond
                                                                                                      200
                                                                                                      "Conversation Code"
                                                                                                      ConversationCodeInfo]
                                                                                                  ConversationCodeInfo))))))))))
                                                      :<|> (Named
                                                              "member-typing-unqualified"
                                                              (Summary
                                                                 "Sending typing notifications"
                                                               :> (Until 'V3
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "update-typing-indicator"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-typing-indicator-updated"
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("typing"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         TypingStatus
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Notification sent"]
                                                                                                            ())))))))))))
                                                            :<|> (Named
                                                                    "member-typing-qualified"
                                                                    (Summary
                                                                       "Sending typing notifications"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "update-typing-indicator"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-typing-indicator-updated"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("typing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           TypingStatus
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "Notification sent"]
                                                                                                              ()))))))))))
                                                                  :<|> (Named
                                                                          "remove-member-unqualified"
                                                                          (Summary
                                                                             "Remove a member from a conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "leave-conversation"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (Until
                                                                                                 'V2
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Target User ID"]
                                                                                                                                     "usr"
                                                                                                                                     UserId
                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                        :<|> (Named
                                                                                "remove-member"
                                                                                (Summary
                                                                                   "Remove a member from a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "leave-conversation"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'RemoveConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("members"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Target User ID"]
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-other-member-unqualified"
                                                                                      (Summary
                                                                                         "Update membership of the specified user (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvMemberNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidTarget
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("members"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Target User ID"]
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                    200
                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                ()))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-other-member"
                                                                                            (Summary
                                                                                               "Update membership of the specified user"
                                                                                             :> (Description
                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvMemberNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidTarget
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("members"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Target User ID"]
                                                                                                                                                           "usr"
                                                                                                                                                           UserId
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                  ())))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name-deprecated"
                                                                                                  (Summary
                                                                                                     "Update conversation name (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationName)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationRename
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Name unchanged"
                                                                                                                                                               "Name updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name-unqualified"
                                                                                                        (Summary
                                                                                                           "Update conversation name (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationName)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("name"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationRename
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                         "Name updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name"
                                                                                                              (Summary
                                                                                                                 "Update conversation name"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationName)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("name"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConversationRename
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                       "Name updated"
                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                       Event)
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                         Event)
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-message-timer"
                                                                                                                          (Summary
                                                                                                                             "Update the message timer for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "update-conversation"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                      (Summary
                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "update-conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("self"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Maybe
                                                                                                                                                                                           Member)))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                        :<|> Named
                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                               (Summary
                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                :> (From
                                                                                                                                                                                      'V5
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "add-members-to-conversation-unqualified2"
        (Summary "Add qualified members to an existing conversation."
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (Until 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> ("v2"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               InviteQualified
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  ConvUpdateResponses
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))))))))
      :<|> (Named
              "add-members-to-conversation"
              (Summary "Add qualified members to an existing conversation."
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (From 'V2
                           :> (CanThrow ('ActionDenied 'AddConversationMember)
                               :> (CanThrow ('ActionDenied 'LeaveConversation)
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidOperation
                                           :> (CanThrow 'TooManyMembers
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'NotConnected
                                                           :> (CanThrow 'MissingLegalholdConsent
                                                               :> (CanThrow NonFederatingBackends
                                                                   :> (CanThrow UnreachableBackends
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 InviteQualified
                                                                                               :> MultiVerb
                                                                                                    'POST
                                                                                                    '[JSON]
                                                                                                    ConvUpdateResponses
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))))))))
            :<|> (Named
                    "join-conversation-by-id-unqualified"
                    (Summary
                       "Join a conversation by its ID (if link access enabled) (deprecated)"
                     :> (Until 'V5
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TooManyMembers
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("join"
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          ConvJoinResponses
                                                                          (UpdateResult
                                                                             Event))))))))))))))
                  :<|> (Named
                          "join-conversation-by-code-unqualified"
                          (Summary "Join a conversation using a reusable code"
                           :> (Description
                                 "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (CanThrow 'CodeNotFound
                                       :> (CanThrow 'InvalidConversationPassword
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'GuestLinksDisabled
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'NotATeamMember
                                                               :> (CanThrow 'TooManyMembers
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> ("join"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         JoinConversationByCode
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            ConvJoinResponses
                                                                                            (UpdateResult
                                                                                               Event)))))))))))))))))
                        :<|> (Named
                                "code-check"
                                (Summary "Check validity of a conversation code."
                                 :> (Description
                                       "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                                     :> (CanThrow 'CodeNotFound
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidConversationPassword
                                                 :> ("conversations"
                                                     :> ("code-check"
                                                         :> (ReqBody '[JSON] ConversationCode
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty 200 "Valid"]
                                                                  ()))))))))
                              :<|> (Named
                                      "create-conversation-code-unqualified@v3"
                                      (Summary "Create or recreate a conversation code"
                                       :> (Until 'V4
                                           :> (DescriptionOAuthScope 'WriteConversationsCode
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow
                                                                 'CreateConversationCodeConflict
                                                               :> (ZUser
                                                                   :> (ZHostOpt
                                                                       :> (ZOptConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> CreateConversationCodeVerb)))))))))))))
                                    :<|> (Named
                                            "create-conversation-code-unqualified"
                                            (Summary "Create or recreate a conversation code"
                                             :> (From 'V4
                                                 :> (DescriptionOAuthScope 'WriteConversationsCode
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'GuestLinksDisabled
                                                                 :> (CanThrow
                                                                       'CreateConversationCodeConflict
                                                                     :> (ZUser
                                                                         :> (ZHostOpt
                                                                             :> (ZOptConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   CreateConversationCodeRequest
                                                                                                 :> CreateConversationCodeVerb))))))))))))))
                                          :<|> (Named
                                                  "get-conversation-guest-links-status"
                                                  (Summary
                                                     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZUser
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("features"
                                                                           :> ("conversationGuestLinks"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       GuestLinksConfig)))))))))
                                                :<|> (Named
                                                        "remove-code-unqualified"
                                                        (Summary "Delete conversation code"
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("code"
                                                                                     :> MultiVerb
                                                                                          'DELETE
                                                                                          '[JSON]
                                                                                          '[Respond
                                                                                              200
                                                                                              "Conversation code deleted."
                                                                                              Event]
                                                                                          Event))))))))
                                                      :<|> (Named
                                                              "get-code"
                                                              (Summary
                                                                 "Get existing conversation code"
                                                               :> (CanThrow 'CodeNotFound
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'GuestLinksDisabled
                                                                               :> (ZHostOpt
                                                                                   :> (ZLocalUser
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("code"
                                                                                                   :> MultiVerb
                                                                                                        'GET
                                                                                                        '[JSON]
                                                                                                        '[Respond
                                                                                                            200
                                                                                                            "Conversation Code"
                                                                                                            ConversationCodeInfo]
                                                                                                        ConversationCodeInfo))))))))))
                                                            :<|> (Named
                                                                    "member-typing-unqualified"
                                                                    (Summary
                                                                       "Sending typing notifications"
                                                                     :> (Until 'V3
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "update-typing-indicator"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-typing-indicator-updated"
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("typing"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               TypingStatus
                                                                                                             :> MultiVerb
                                                                                                                  'POST
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Notification sent"]
                                                                                                                  ())))))))))))
                                                                  :<|> (Named
                                                                          "member-typing-qualified"
                                                                          (Summary
                                                                             "Sending typing notifications"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "update-typing-indicator"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-typing-indicator-updated"
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("typing"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 TypingStatus
                                                                                                               :> MultiVerb
                                                                                                                    'POST
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "Notification sent"]
                                                                                                                    ()))))))))))
                                                                        :<|> (Named
                                                                                "remove-member-unqualified"
                                                                                (Summary
                                                                                   "Remove a member from a conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "leave-conversation"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (Until
                                                                                                       'V2
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("members"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Target User ID"]
                                                                                                                                           "usr"
                                                                                                                                           UserId
                                                                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                                                                              :<|> (Named
                                                                                      "remove-member"
                                                                                      (Summary
                                                                                         "Remove a member from a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "leave-conversation"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'RemoveConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("members"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Target User ID"]
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-other-member-unqualified"
                                                                                            (Summary
                                                                                               "Update membership of the specified user (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvMemberNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidTarget
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("members"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Target User ID"]
                                                                                                                                                               "usr"
                                                                                                                                                               UserId
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                          200
                                                                                                                                                                          "Membership updated"]
                                                                                                                                                                      ()))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-other-member"
                                                                                                  (Summary
                                                                                                     "Update membership of the specified user"
                                                                                                   :> (Description
                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-conversation-updated"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-mls-message-sent"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvMemberNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyOtherConversationMember)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidTarget
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("members"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Target User ID"]
                                                                                                                                                                 "usr"
                                                                                                                                                                 UserId
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     OtherMemberUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                            200
                                                                                                                                                                            "Membership updated"]
                                                                                                                                                                        ())))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name-deprecated"
                                                                                                        (Summary
                                                                                                           "Update conversation name (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationName)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationRename
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Name unchanged"
                                                                                                                                                                     "Name updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update conversation name (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationName)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("name"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationRename
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Name unchanged"
                                                                                                                                                                               "Name updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-name"
                                                                                                                    (Summary
                                                                                                                       "Update conversation name"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationName)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("name"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConversationRename
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                             "Name updated"
                                                                                                                                                                             "Name unchanged"
                                                                                                                                                                             Event)
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-message-timer-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update the message timer for a conversation (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Brig
                                                                                                                                                 "get-users-by-ids"
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("message-timer"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                                                               "Message timer updated"
                                                                                                                                                                                               Event)
                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                               Event)))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-message-timer"
                                                                                                                                (Summary
                                                                                                                                   "Update the message timer for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "update-conversation"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-receipt-mode"
                                                                                                                                            (Summary
                                                                                                                                               "Update receipt mode for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Galley
                                                                                                                                                           "update-conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Brig
                                                                                                                                                               "get-users-by-ids"
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                                 ConvId
                                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                                         'V2
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                                               Event)
                                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access@v2"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-access"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update access modes for a conversation"
                                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                                     'Galley
                                                                                                                                                                     "on-conversation-updated"
                                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                                         'Galley
                                                                                                                                                                         "on-mls-message-sent"
                                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                                             'Brig
                                                                                                                                                                             "get-users-by-ids"
                                                                                                                                                                           :> (From
                                                                                                                                                                                 'V3
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> (ZConn
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                                                       Event)
                                                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (Maybe
                                                                                                                                                                                                 Member)))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                                                                           :> (Deprecated
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                                           :> (ZConn
                                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                                         '[Description
                                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                                         "cnv"
                                                                                                                                                                                                         ConvId
                                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                                        200
                                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                                    ()))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                "update-conversation-self"
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "Update self membership properties"
                                                                                                                                                                                 :> (Description
                                                                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("self"
                                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                                                          200
                                                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                                                      ())))))))))
                                                                                                                                                                              :<|> Named
                                                                                                                                                                                     "update-conversation-protocol"
                                                                                                                                                                                     (Summary
                                                                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                                                                      :> (From
                                                                                                                                                                                            'V5
                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'ConvNotFound
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            ('ActionDenied
                                                                                                                                                                                                               'LeaveConversation)
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'InvalidOperation
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                                                                '[Description
                                                                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                                                                ConvId
                                                                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"add-members-to-conversation" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> InviteQualified
 -> Sem
      '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
        Error (Tagged ('ActionDenied 'LeaveConversation) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'TooManyMembers ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
        Error (Tagged 'MissingLegalholdConsent ()),
        Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
        SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
        ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
        BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-updated",
 (HasAnnotation 'Remote "galley" "on-mls-message-sent",
  () :: Constraint)) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> InviteQualified
-> Sem
     '[Error (Tagged ('ActionDenied 'AddConversationMember) ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'TooManyMembers ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'NotConnected ()),
       Error (Tagged 'MissingLegalholdConsent ()),
       Error NonFederatingBackends, Error UnreachableBackends, BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'AddConversationMember) ())) r,
 Member (Error (Tagged ('ActionDenied 'LeaveConversation) ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotConnected ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member (Error (Tagged 'MissingLegalholdConsent ())) r,
 Member (Error FederationError) r,
 Member (Error NonFederatingBackends) r,
 Member (Error UnreachableBackends) r, Member ExternalAccess r,
 Member FederatorAccess r, Member NotificationSubsystem r,
 Member (Input Env) r, Member (Input Opts) r,
 Member (Input UTCTime) r, Member LegalHoldStore r,
 Member MemberStore r, Member ProposalStore r, Member Random r,
 Member SubConversationStore r, Member TeamStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> InviteQualified
-> Sem r (UpdateResult Event)
addMembers)
    API
  (Named
     "add-members-to-conversation"
     (Summary "Add qualified members to an existing conversation."
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (From 'V2
                  :> (CanThrow ('ActionDenied 'AddConversationMember)
                      :> (CanThrow ('ActionDenied 'LeaveConversation)
                          :> (CanThrow 'ConvNotFound
                              :> (CanThrow 'InvalidOperation
                                  :> (CanThrow 'TooManyMembers
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow 'NotConnected
                                                  :> (CanThrow 'MissingLegalholdConsent
                                                      :> (CanThrow NonFederatingBackends
                                                          :> (CanThrow UnreachableBackends
                                                              :> (ZLocalUser
                                                                  :> (ZConn
                                                                      :> ("conversations"
                                                                          :> (QualifiedCapture
                                                                                "cnv" ConvId
                                                                              :> ("members"
                                                                                  :> (ReqBody
                                                                                        '[JSON]
                                                                                        InviteQualified
                                                                                      :> MultiVerb
                                                                                           'POST
                                                                                           '[JSON]
                                                                                           ConvUpdateResponses
                                                                                           (UpdateResult
                                                                                              Event)))))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "join-conversation-by-id-unqualified"
        (Summary
           "Join a conversation by its ID (if link access enabled) (deprecated)"
         :> (Until 'V5
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TooManyMembers
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("join"
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              ConvJoinResponses
                                                              (UpdateResult Event))))))))))))))
      :<|> (Named
              "join-conversation-by-code-unqualified"
              (Summary "Join a conversation using a reusable code"
               :> (Description
                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (CanThrow 'CodeNotFound
                           :> (CanThrow 'InvalidConversationPassword
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'GuestLinksDisabled
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TooManyMembers
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> ("join"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             JoinConversationByCode
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                ConvJoinResponses
                                                                                (UpdateResult
                                                                                   Event)))))))))))))))))
            :<|> (Named
                    "code-check"
                    (Summary "Check validity of a conversation code."
                     :> (Description
                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                         :> (CanThrow 'CodeNotFound
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidConversationPassword
                                     :> ("conversations"
                                         :> ("code-check"
                                             :> (ReqBody '[JSON] ConversationCode
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Valid"]
                                                      ()))))))))
                  :<|> (Named
                          "create-conversation-code-unqualified@v3"
                          (Summary "Create or recreate a conversation code"
                           :> (Until 'V4
                               :> (DescriptionOAuthScope 'WriteConversationsCode
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'CreateConversationCodeConflict
                                                   :> (ZUser
                                                       :> (ZHostOpt
                                                           :> (ZOptConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> CreateConversationCodeVerb)))))))))))))
                        :<|> (Named
                                "create-conversation-code-unqualified"
                                (Summary "Create or recreate a conversation code"
                                 :> (From 'V4
                                     :> (DescriptionOAuthScope 'WriteConversationsCode
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'CreateConversationCodeConflict
                                                         :> (ZUser
                                                             :> (ZHostOpt
                                                                 :> (ZOptConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       CreateConversationCodeRequest
                                                                                     :> CreateConversationCodeVerb))))))))))))))
                              :<|> (Named
                                      "get-conversation-guest-links-status"
                                      (Summary
                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZUser
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("features"
                                                               :> ("conversationGuestLinks"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           GuestLinksConfig)))))))))
                                    :<|> (Named
                                            "remove-code-unqualified"
                                            (Summary "Delete conversation code"
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("code"
                                                                         :> MultiVerb
                                                                              'DELETE
                                                                              '[JSON]
                                                                              '[Respond
                                                                                  200
                                                                                  "Conversation code deleted."
                                                                                  Event]
                                                                              Event))))))))
                                          :<|> (Named
                                                  "get-code"
                                                  (Summary "Get existing conversation code"
                                                   :> (CanThrow 'CodeNotFound
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'GuestLinksDisabled
                                                                   :> (ZHostOpt
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[Respond
                                                                                                200
                                                                                                "Conversation Code"
                                                                                                ConversationCodeInfo]
                                                                                            ConversationCodeInfo))))))))))
                                                :<|> (Named
                                                        "member-typing-unqualified"
                                                        (Summary "Sending typing notifications"
                                                         :> (Until 'V3
                                                             :> (MakesFederatedCall
                                                                   'Galley "update-typing-indicator"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-typing-indicator-updated"
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("typing"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   TypingStatus
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Notification sent"]
                                                                                                      ())))))))))))
                                                      :<|> (Named
                                                              "member-typing-qualified"
                                                              (Summary
                                                                 "Sending typing notifications"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "update-typing-indicator"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-typing-indicator-updated"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("typing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     TypingStatus
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "Notification sent"]
                                                                                                        ()))))))))))
                                                            :<|> (Named
                                                                    "remove-member-unqualified"
                                                                    (Summary
                                                                       "Remove a member from a conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "leave-conversation"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (Until 'V2
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Target User ID"]
                                                                                                                               "usr"
                                                                                                                               UserId
                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                  :<|> (Named
                                                                          "remove-member"
                                                                          (Summary
                                                                             "Remove a member from a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "leave-conversation"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'RemoveConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("members"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Target User ID"]
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                        :<|> (Named
                                                                                "update-other-member-unqualified"
                                                                                (Summary
                                                                                   "Update membership of the specified user (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvMemberNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidTarget
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("members"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Target User ID"]
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[RespondEmpty
                                                                                                                                                              200
                                                                                                                                                              "Membership updated"]
                                                                                                                                                          ()))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-other-member"
                                                                                      (Summary
                                                                                         "Update membership of the specified user"
                                                                                       :> (Description
                                                                                             "**Note**: at least one field has to be provided."
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvMemberNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidTarget
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("members"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Target User ID"]
                                                                                                                                                     "usr"
                                                                                                                                                     UserId
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Membership updated"]
                                                                                                                                                            ())))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name-deprecated"
                                                                                            (Summary
                                                                                               "Update conversation name (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationName)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationRename
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Name unchanged"
                                                                                                                                                         "Name updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name-unqualified"
                                                                                                  (Summary
                                                                                                     "Update conversation name (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationName)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("name"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationRename
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                   "Name updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name"
                                                                                                        (Summary
                                                                                                           "Update conversation name"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationName)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("name"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConversationRename
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              (UpdateResponses
                                                                                                                                                                 "Name updated"
                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                 Event)
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                   Event)
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-message-timer"
                                                                                                                    (Summary
                                                                                                                       "Update the message timer for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "update-conversation"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                (Summary
                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "update-conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                             'V2
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("self"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Maybe
                                                                                                                                                                                     Member)))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                  :<|> Named
                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                         (Summary
                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                          :> (From
                                                                                                                                                                                'V5
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "add-members-to-conversation"
        (Summary "Add qualified members to an existing conversation."
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (From 'V2
                     :> (CanThrow ('ActionDenied 'AddConversationMember)
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidOperation
                                     :> (CanThrow 'TooManyMembers
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'NotConnected
                                                     :> (CanThrow 'MissingLegalholdConsent
                                                         :> (CanThrow NonFederatingBackends
                                                             :> (CanThrow UnreachableBackends
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture
                                                                                   "cnv" ConvId
                                                                                 :> ("members"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           InviteQualified
                                                                                         :> MultiVerb
                                                                                              'POST
                                                                                              '[JSON]
                                                                                              ConvUpdateResponses
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))))))))
      :<|> (Named
              "join-conversation-by-id-unqualified"
              (Summary
                 "Join a conversation by its ID (if link access enabled) (deprecated)"
               :> (Until 'V5
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'InvalidOperation
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow 'TooManyMembers
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("join"
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    ConvJoinResponses
                                                                    (UpdateResult
                                                                       Event))))))))))))))
            :<|> (Named
                    "join-conversation-by-code-unqualified"
                    (Summary "Join a conversation using a reusable code"
                     :> (Description
                           "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (CanThrow 'CodeNotFound
                                 :> (CanThrow 'InvalidConversationPassword
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'GuestLinksDisabled
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'NotATeamMember
                                                         :> (CanThrow 'TooManyMembers
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> ("join"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   JoinConversationByCode
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      ConvJoinResponses
                                                                                      (UpdateResult
                                                                                         Event)))))))))))))))))
                  :<|> (Named
                          "code-check"
                          (Summary "Check validity of a conversation code."
                           :> (Description
                                 "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                               :> (CanThrow 'CodeNotFound
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'InvalidConversationPassword
                                           :> ("conversations"
                                               :> ("code-check"
                                                   :> (ReqBody '[JSON] ConversationCode
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty 200 "Valid"]
                                                            ()))))))))
                        :<|> (Named
                                "create-conversation-code-unqualified@v3"
                                (Summary "Create or recreate a conversation code"
                                 :> (Until 'V4
                                     :> (DescriptionOAuthScope 'WriteConversationsCode
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'CreateConversationCodeConflict
                                                         :> (ZUser
                                                             :> (ZHostOpt
                                                                 :> (ZOptConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> CreateConversationCodeVerb)))))))))))))
                              :<|> (Named
                                      "create-conversation-code-unqualified"
                                      (Summary "Create or recreate a conversation code"
                                       :> (From 'V4
                                           :> (DescriptionOAuthScope 'WriteConversationsCode
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'GuestLinksDisabled
                                                           :> (CanThrow
                                                                 'CreateConversationCodeConflict
                                                               :> (ZUser
                                                                   :> (ZHostOpt
                                                                       :> (ZOptConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             CreateConversationCodeRequest
                                                                                           :> CreateConversationCodeVerb))))))))))))))
                                    :<|> (Named
                                            "get-conversation-guest-links-status"
                                            (Summary
                                               "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZUser
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("features"
                                                                     :> ("conversationGuestLinks"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 GuestLinksConfig)))))))))
                                          :<|> (Named
                                                  "remove-code-unqualified"
                                                  (Summary "Delete conversation code"
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("code"
                                                                               :> MultiVerb
                                                                                    'DELETE
                                                                                    '[JSON]
                                                                                    '[Respond
                                                                                        200
                                                                                        "Conversation code deleted."
                                                                                        Event]
                                                                                    Event))))))))
                                                :<|> (Named
                                                        "get-code"
                                                        (Summary "Get existing conversation code"
                                                         :> (CanThrow 'CodeNotFound
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow
                                                                           'GuestLinksDisabled
                                                                         :> (ZHostOpt
                                                                             :> (ZLocalUser
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("code"
                                                                                             :> MultiVerb
                                                                                                  'GET
                                                                                                  '[JSON]
                                                                                                  '[Respond
                                                                                                      200
                                                                                                      "Conversation Code"
                                                                                                      ConversationCodeInfo]
                                                                                                  ConversationCodeInfo))))))))))
                                                      :<|> (Named
                                                              "member-typing-unqualified"
                                                              (Summary
                                                                 "Sending typing notifications"
                                                               :> (Until 'V3
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "update-typing-indicator"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-typing-indicator-updated"
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("typing"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         TypingStatus
                                                                                                       :> MultiVerb
                                                                                                            'POST
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Notification sent"]
                                                                                                            ())))))))))))
                                                            :<|> (Named
                                                                    "member-typing-qualified"
                                                                    (Summary
                                                                       "Sending typing notifications"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "update-typing-indicator"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-typing-indicator-updated"
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("typing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           TypingStatus
                                                                                                         :> MultiVerb
                                                                                                              'POST
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "Notification sent"]
                                                                                                              ()))))))))))
                                                                  :<|> (Named
                                                                          "remove-member-unqualified"
                                                                          (Summary
                                                                             "Remove a member from a conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "leave-conversation"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (Until
                                                                                                 'V2
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("members"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Target User ID"]
                                                                                                                                     "usr"
                                                                                                                                     UserId
                                                                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                                                                        :<|> (Named
                                                                                "remove-member"
                                                                                (Summary
                                                                                   "Remove a member from a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "leave-conversation"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'RemoveConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("members"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Target User ID"]
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> RemoveFromConversationVerb))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-other-member-unqualified"
                                                                                      (Summary
                                                                                         "Update membership of the specified user (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvMemberNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyOtherConversationMember)
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidTarget
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("members"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Target User ID"]
                                                                                                                                                         "usr"
                                                                                                                                                         UserId
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             OtherMemberUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                    200
                                                                                                                                                                    "Membership updated"]
                                                                                                                                                                ()))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-other-member"
                                                                                            (Summary
                                                                                               "Update membership of the specified user"
                                                                                             :> (Description
                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-conversation-updated"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-mls-message-sent"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvMemberNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyOtherConversationMember)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidTarget
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("members"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Target User ID"]
                                                                                                                                                           "usr"
                                                                                                                                                           UserId
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               OtherMemberUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                      200
                                                                                                                                                                      "Membership updated"]
                                                                                                                                                                  ())))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name-deprecated"
                                                                                                  (Summary
                                                                                                     "Update conversation name (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationName)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationRename
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Name unchanged"
                                                                                                                                                               "Name updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name-unqualified"
                                                                                                        (Summary
                                                                                                           "Update conversation name (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationName)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("name"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationRename
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Name unchanged"
                                                                                                                                                                         "Name updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-name"
                                                                                                              (Summary
                                                                                                                 "Update conversation name"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationName)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("name"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConversationRename
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                       "Name updated"
                                                                                                                                                                       "Name unchanged"
                                                                                                                                                                       Event)
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-message-timer-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update the message timer for a conversation (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Brig
                                                                                                                                           "get-users-by-ids"
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("message-timer"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                                                         "Message timer updated"
                                                                                                                                                                                         Event)
                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                         Event)))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-message-timer"
                                                                                                                          (Summary
                                                                                                                             "Update the message timer for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("message-timer"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "on-conversation-updated"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "update-conversation"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-receipt-mode"
                                                                                                                                      (Summary
                                                                                                                                         "Update receipt mode for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Galley
                                                                                                                                                     "update-conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Brig
                                                                                                                                                         "get-users-by-ids"
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                                     :> (Capture'
                                                                                                                                                                                                           '[Description
                                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                                           "cnv"
                                                                                                                                                                                                           ConvId
                                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                                         Event)
                                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                                         Event)))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access@v2"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-access"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update access modes for a conversation"
                                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                                               'Galley
                                                                                                                                                               "on-conversation-updated"
                                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                                   'Galley
                                                                                                                                                                   "on-mls-message-sent"
                                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                                       'Brig
                                                                                                                                                                       "get-users-by-ids"
                                                                                                                                                                     :> (From
                                                                                                                                                                           'V3
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> (ZConn
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                                                 Event)
                                                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-conversation-self-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("self"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (Maybe
                                                                                                                                                                                           Member)))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                                                                     :> (Deprecated
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                                     :> (ZConn
                                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                                   '[Description
                                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                                   "cnv"
                                                                                                                                                                                                   ConvId
                                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                                              'PUT
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                                  200
                                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                                              ()))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          "update-conversation-self"
                                                                                                                                                                          (Summary
                                                                                                                                                                             "Update self membership properties"
                                                                                                                                                                           :> (Description
                                                                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                                       :> (ZConn
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("self"
                                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             MemberUpdate
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                                                    200
                                                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                                                ())))))))))
                                                                                                                                                                        :<|> Named
                                                                                                                                                                               "update-conversation-protocol"
                                                                                                                                                                               (Summary
                                                                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                                                                :> (From
                                                                                                                                                                                      'V5
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'ConvNotFound
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      ('ActionDenied
                                                                                                                                                                                                         'LeaveConversation)
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'InvalidOperation
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                                                                          '[Description
                                                                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                                                                          "cnv"
                                                                                                                                                                                                                                          ConvId
                                                                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"join-conversation-by-id-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> Sem
      '[Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-updated",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member MemberStore r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> Sem r (UpdateResult Event)
joinConversationById)
    API
  (Named
     "join-conversation-by-id-unqualified"
     (Summary
        "Join a conversation by its ID (if link access enabled) (deprecated)"
      :> (Until 'V5
          :> (MakesFederatedCall 'Galley "on-conversation-updated"
              :> (CanThrow 'ConvAccessDenied
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'InvalidOperation
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TooManyMembers
                                  :> (ZLocalUser
                                      :> (ZConn
                                          :> ("conversations"
                                              :> (Capture'
                                                    '[Description "Conversation ID"] "cnv" ConvId
                                                  :> ("join"
                                                      :> MultiVerb
                                                           'POST
                                                           '[JSON]
                                                           ConvJoinResponses
                                                           (UpdateResult Event)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "join-conversation-by-code-unqualified"
        (Summary "Join a conversation using a reusable code"
         :> (Description
               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (CanThrow 'CodeNotFound
                     :> (CanThrow 'InvalidConversationPassword
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'GuestLinksDisabled
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TooManyMembers
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> ("join"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       JoinConversationByCode
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          ConvJoinResponses
                                                                          (UpdateResult
                                                                             Event)))))))))))))))))
      :<|> (Named
              "code-check"
              (Summary "Check validity of a conversation code."
               :> (Description
                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                   :> (CanThrow 'CodeNotFound
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'InvalidConversationPassword
                               :> ("conversations"
                                   :> ("code-check"
                                       :> (ReqBody '[JSON] ConversationCode
                                           :> MultiVerb
                                                'POST '[JSON] '[RespondEmpty 200 "Valid"] ()))))))))
            :<|> (Named
                    "create-conversation-code-unqualified@v3"
                    (Summary "Create or recreate a conversation code"
                     :> (Until 'V4
                         :> (DescriptionOAuthScope 'WriteConversationsCode
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'CreateConversationCodeConflict
                                             :> (ZUser
                                                 :> (ZHostOpt
                                                     :> (ZOptConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> CreateConversationCodeVerb)))))))))))))
                  :<|> (Named
                          "create-conversation-code-unqualified"
                          (Summary "Create or recreate a conversation code"
                           :> (From 'V4
                               :> (DescriptionOAuthScope 'WriteConversationsCode
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'CreateConversationCodeConflict
                                                   :> (ZUser
                                                       :> (ZHostOpt
                                                           :> (ZOptConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 CreateConversationCodeRequest
                                                                               :> CreateConversationCodeVerb))))))))))))))
                        :<|> (Named
                                "get-conversation-guest-links-status"
                                (Summary
                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZUser
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("features"
                                                         :> ("conversationGuestLinks"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     GuestLinksConfig)))))))))
                              :<|> (Named
                                      "remove-code-unqualified"
                                      (Summary "Delete conversation code"
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("code"
                                                                   :> MultiVerb
                                                                        'DELETE
                                                                        '[JSON]
                                                                        '[Respond
                                                                            200
                                                                            "Conversation code deleted."
                                                                            Event]
                                                                        Event))))))))
                                    :<|> (Named
                                            "get-code"
                                            (Summary "Get existing conversation code"
                                             :> (CanThrow 'CodeNotFound
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'GuestLinksDisabled
                                                             :> (ZHostOpt
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[Respond
                                                                                          200
                                                                                          "Conversation Code"
                                                                                          ConversationCodeInfo]
                                                                                      ConversationCodeInfo))))))))))
                                          :<|> (Named
                                                  "member-typing-unqualified"
                                                  (Summary "Sending typing notifications"
                                                   :> (Until 'V3
                                                       :> (MakesFederatedCall
                                                             'Galley "update-typing-indicator"
                                                           :> (MakesFederatedCall
                                                                 'Galley
                                                                 "on-typing-indicator-updated"
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("typing"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             TypingStatus
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Notification sent"]
                                                                                                ())))))))))))
                                                :<|> (Named
                                                        "member-typing-qualified"
                                                        (Summary "Sending typing notifications"
                                                         :> (MakesFederatedCall
                                                               'Galley "update-typing-indicator"
                                                             :> (MakesFederatedCall
                                                                   'Galley
                                                                   "on-typing-indicator-updated"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("typing"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               TypingStatus
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "Notification sent"]
                                                                                                  ()))))))))))
                                                      :<|> (Named
                                                              "remove-member-unqualified"
                                                              (Summary
                                                                 "Remove a member from a conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley "leave-conversation"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (Until 'V2
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Target User ID"]
                                                                                                                         "usr"
                                                                                                                         UserId
                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                            :<|> (Named
                                                                    "remove-member"
                                                                    (Summary
                                                                       "Remove a member from a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "leave-conversation"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'RemoveConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("members"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Target User ID"]
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                  :<|> (Named
                                                                          "update-other-member-unqualified"
                                                                          (Summary
                                                                             "Update membership of the specified user (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'ConvMemberNotFound
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidTarget
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("members"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Target User ID"]
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 OtherMemberUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[RespondEmpty
                                                                                                                                                        200
                                                                                                                                                        "Membership updated"]
                                                                                                                                                    ()))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-other-member"
                                                                                (Summary
                                                                                   "Update membership of the specified user"
                                                                                 :> (Description
                                                                                       "**Note**: at least one field has to be provided."
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvMemberNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidTarget
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("members"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Target User ID"]
                                                                                                                                               "usr"
                                                                                                                                               UserId
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Membership updated"]
                                                                                                                                                      ())))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name-deprecated"
                                                                                      (Summary
                                                                                         "Update conversation name (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationName)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationRename
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Name unchanged"
                                                                                                                                                   "Name updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name-unqualified"
                                                                                            (Summary
                                                                                               "Update conversation name (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationName)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("name"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationRename
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Name unchanged"
                                                                                                                                                             "Name updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name"
                                                                                                  (Summary
                                                                                                     "Update conversation name"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationName)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("name"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConversationRename
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        (UpdateResponses
                                                                                                                                                           "Name updated"
                                                                                                                                                           "Name unchanged"
                                                                                                                                                           Event)
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                        (Summary
                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                             Event)
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-message-timer"
                                                                                                              (Summary
                                                                                                                 "Update the message timer for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("message-timer"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "update-conversation"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                          (Summary
                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "update-conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                       'V2
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (From
                                                                                                                                                               'V3
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("self"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Maybe
                                                                                                                                                                               Member)))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-self"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                    ())))))))))
                                                                                                                                                            :<|> Named
                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                   (Summary
                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                    :> (From
                                                                                                                                                                          'V5
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "join-conversation-by-id-unqualified"
        (Summary
           "Join a conversation by its ID (if link access enabled) (deprecated)"
         :> (Until 'V5
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'InvalidOperation
                             :> (CanThrow 'NotATeamMember
                                 :> (CanThrow 'TooManyMembers
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("join"
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              ConvJoinResponses
                                                              (UpdateResult Event))))))))))))))
      :<|> (Named
              "join-conversation-by-code-unqualified"
              (Summary "Join a conversation using a reusable code"
               :> (Description
                     "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (CanThrow 'CodeNotFound
                           :> (CanThrow 'InvalidConversationPassword
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'GuestLinksDisabled
                                           :> (CanThrow 'InvalidOperation
                                               :> (CanThrow 'NotATeamMember
                                                   :> (CanThrow 'TooManyMembers
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> ("join"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             JoinConversationByCode
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                ConvJoinResponses
                                                                                (UpdateResult
                                                                                   Event)))))))))))))))))
            :<|> (Named
                    "code-check"
                    (Summary "Check validity of a conversation code."
                     :> (Description
                           "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                         :> (CanThrow 'CodeNotFound
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'InvalidConversationPassword
                                     :> ("conversations"
                                         :> ("code-check"
                                             :> (ReqBody '[JSON] ConversationCode
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Valid"]
                                                      ()))))))))
                  :<|> (Named
                          "create-conversation-code-unqualified@v3"
                          (Summary "Create or recreate a conversation code"
                           :> (Until 'V4
                               :> (DescriptionOAuthScope 'WriteConversationsCode
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'CreateConversationCodeConflict
                                                   :> (ZUser
                                                       :> (ZHostOpt
                                                           :> (ZOptConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> CreateConversationCodeVerb)))))))))))))
                        :<|> (Named
                                "create-conversation-code-unqualified"
                                (Summary "Create or recreate a conversation code"
                                 :> (From 'V4
                                     :> (DescriptionOAuthScope 'WriteConversationsCode
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'GuestLinksDisabled
                                                     :> (CanThrow 'CreateConversationCodeConflict
                                                         :> (ZUser
                                                             :> (ZHostOpt
                                                                 :> (ZOptConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       CreateConversationCodeRequest
                                                                                     :> CreateConversationCodeVerb))))))))))))))
                              :<|> (Named
                                      "get-conversation-guest-links-status"
                                      (Summary
                                         "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZUser
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("features"
                                                               :> ("conversationGuestLinks"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           GuestLinksConfig)))))))))
                                    :<|> (Named
                                            "remove-code-unqualified"
                                            (Summary "Delete conversation code"
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("code"
                                                                         :> MultiVerb
                                                                              'DELETE
                                                                              '[JSON]
                                                                              '[Respond
                                                                                  200
                                                                                  "Conversation code deleted."
                                                                                  Event]
                                                                              Event))))))))
                                          :<|> (Named
                                                  "get-code"
                                                  (Summary "Get existing conversation code"
                                                   :> (CanThrow 'CodeNotFound
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'GuestLinksDisabled
                                                                   :> (ZHostOpt
                                                                       :> (ZLocalUser
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("code"
                                                                                       :> MultiVerb
                                                                                            'GET
                                                                                            '[JSON]
                                                                                            '[Respond
                                                                                                200
                                                                                                "Conversation Code"
                                                                                                ConversationCodeInfo]
                                                                                            ConversationCodeInfo))))))))))
                                                :<|> (Named
                                                        "member-typing-unqualified"
                                                        (Summary "Sending typing notifications"
                                                         :> (Until 'V3
                                                             :> (MakesFederatedCall
                                                                   'Galley "update-typing-indicator"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-typing-indicator-updated"
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("typing"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   TypingStatus
                                                                                                 :> MultiVerb
                                                                                                      'POST
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Notification sent"]
                                                                                                      ())))))))))))
                                                      :<|> (Named
                                                              "member-typing-qualified"
                                                              (Summary
                                                                 "Sending typing notifications"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "update-typing-indicator"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-typing-indicator-updated"
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("typing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     TypingStatus
                                                                                                   :> MultiVerb
                                                                                                        'POST
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "Notification sent"]
                                                                                                        ()))))))))))
                                                            :<|> (Named
                                                                    "remove-member-unqualified"
                                                                    (Summary
                                                                       "Remove a member from a conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "leave-conversation"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (Until 'V2
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("members"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Target User ID"]
                                                                                                                               "usr"
                                                                                                                               UserId
                                                                                                                             :> RemoveFromConversationVerb)))))))))))))))
                                                                  :<|> (Named
                                                                          "remove-member"
                                                                          (Summary
                                                                             "Remove a member from a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "leave-conversation"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'RemoveConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("members"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Target User ID"]
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> RemoveFromConversationVerb))))))))))))))
                                                                        :<|> (Named
                                                                                "update-other-member-unqualified"
                                                                                (Summary
                                                                                   "Update membership of the specified user (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvMemberNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyOtherConversationMember)
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidTarget
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("members"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Target User ID"]
                                                                                                                                                   "usr"
                                                                                                                                                   UserId
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       OtherMemberUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[RespondEmpty
                                                                                                                                                              200
                                                                                                                                                              "Membership updated"]
                                                                                                                                                          ()))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-other-member"
                                                                                      (Summary
                                                                                         "Update membership of the specified user"
                                                                                       :> (Description
                                                                                             "**Note**: at least one field has to be provided."
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-conversation-updated"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-mls-message-sent"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvMemberNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyOtherConversationMember)
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidTarget
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("members"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Target User ID"]
                                                                                                                                                     "usr"
                                                                                                                                                     UserId
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         OtherMemberUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                200
                                                                                                                                                                "Membership updated"]
                                                                                                                                                            ())))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name-deprecated"
                                                                                            (Summary
                                                                                               "Update conversation name (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationName)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationRename
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Name unchanged"
                                                                                                                                                         "Name updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name-unqualified"
                                                                                                  (Summary
                                                                                                     "Update conversation name (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationName)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("name"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationRename
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Name unchanged"
                                                                                                                                                                   "Name updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-name"
                                                                                                        (Summary
                                                                                                           "Update conversation name"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationName)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("name"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConversationRename
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              (UpdateResponses
                                                                                                                                                                 "Name updated"
                                                                                                                                                                 "Name unchanged"
                                                                                                                                                                 Event)
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-message-timer-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update the message timer for a conversation (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Brig
                                                                                                                                     "get-users-by-ids"
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("message-timer"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                                                   "Message timer updated"
                                                                                                                                                                                   Event)
                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                   Event)))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-message-timer"
                                                                                                                    (Summary
                                                                                                                       "Update the message timer for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("message-timer"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-receipt-mode-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "on-conversation-updated"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-mls-message-sent"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "update-conversation"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-receipt-mode"
                                                                                                                                (Summary
                                                                                                                                   "Update receipt mode for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Galley
                                                                                                                                               "update-conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Brig
                                                                                                                                                   "get-users-by-ids"
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             ('ActionDenied
                                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                                               :> (Capture'
                                                                                                                                                                                                     '[Description
                                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                                     "cnv"
                                                                                                                                                                                                     ConvId
                                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                                             'V2
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                                'PUT
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                                   Event)
                                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                                   Event)))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access@v2"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V3
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-access"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update access modes for a conversation"
                                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                                         'Galley
                                                                                                                                                         "on-conversation-updated"
                                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                                             'Galley
                                                                                                                                                             "on-mls-message-sent"
                                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                                 'Brig
                                                                                                                                                                 "get-users-by-ids"
                                                                                                                                                               :> (From
                                                                                                                                                                     'V3
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> (ZConn
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 'InvalidOperation
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                                                             '[Description
                                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                                             "cnv"
                                                                                                                                                                                                             ConvId
                                                                                                                                                                                                           :> ("access"
                                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                                                           Event)
                                                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                                                           Event))))))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-conversation-self-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Get self membership properties (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("self"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (Maybe
                                                                                                                                                                                     Member)))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-self-unqualified"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                                                                               :> (Deprecated
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvNotFound
                                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                                               :> (ZConn
                                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                                       :> (Capture'
                                                                                                                                                                                             '[Description
                                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                                             "cnv"
                                                                                                                                                                                             ConvId
                                                                                                                                                                                           :> ("self"
                                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                                        'PUT
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                                            200
                                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                                        ()))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    "update-conversation-self"
                                                                                                                                                                    (Summary
                                                                                                                                                                       "Update self membership properties"
                                                                                                                                                                     :> (Description
                                                                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                                 :> (ZConn
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("self"
                                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       MemberUpdate
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                                                              200
                                                                                                                                                                                                              "Update successful"]
                                                                                                                                                                                                          ())))))))))
                                                                                                                                                                  :<|> Named
                                                                                                                                                                         "update-conversation-protocol"
                                                                                                                                                                         (Summary
                                                                                                                                                                            "Update the protocol of the conversation"
                                                                                                                                                                          :> (From
                                                                                                                                                                                'V5
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'ConvNotFound
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                ('ActionDenied
                                                                                                                                                                                                   'LeaveConversation)
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'InvalidOperation
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                                                                      :> (ZConn
                                                                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                                                                    '[Description
                                                                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                                                                    "cnv"
                                                                                                                                                                                                                                    ConvId
                                                                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                                                                               'PUT
                                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"join-conversation-by-code-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  () :: Constraint) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> JoinConversationByCode
 -> Sem
      '[Error (Tagged 'CodeNotFound ()),
        Error (Tagged 'InvalidConversationPassword ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'GuestLinksDisabled ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'NotATeamMember ()),
        Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> JoinConversationByCode
-> Sem
     '[Error (Tagged 'CodeNotFound ()),
       Error (Tagged 'InvalidConversationPassword ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed (HasAnnotation 'Remote "galley" "on-conversation-updated",
 () :: Constraint) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> JoinConversationByCode
-> Sem
     '[Error (Tagged 'CodeNotFound ()),
       Error (Tagged 'InvalidConversationPassword ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
QualifiedWithTag 'QLocal UserId
-> ConnId
-> JoinConversationByCode
-> Sem
     '[Error (Tagged 'CodeNotFound ()),
       Error (Tagged 'InvalidConversationPassword ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged 'TooManyMembers ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member CodeStore r, Member ConversationStore r,
 Member (Error FederationError) r,
 Member (Error (Tagged 'CodeNotFound ())) r,
 Member (Error (Tagged 'InvalidConversationPassword ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'GuestLinksDisabled ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TooManyMembers ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input Opts) r, Member (Input UTCTime) r,
 Member MemberStore r, Member TeamStore r,
 Member TeamFeatureStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> JoinConversationByCode -> Sem r (UpdateResult Event)
joinConversationByReusableCode)
    API
  (Named
     "join-conversation-by-code-unqualified"
     (Summary "Join a conversation using a reusable code"
      :> (Description
            "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
          :> (MakesFederatedCall 'Galley "on-conversation-updated"
              :> (CanThrow 'CodeNotFound
                  :> (CanThrow 'InvalidConversationPassword
                      :> (CanThrow 'ConvAccessDenied
                          :> (CanThrow 'ConvNotFound
                              :> (CanThrow 'GuestLinksDisabled
                                  :> (CanThrow 'InvalidOperation
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TooManyMembers
                                              :> (ZLocalUser
                                                  :> (ZConn
                                                      :> ("conversations"
                                                          :> ("join"
                                                              :> (ReqBody
                                                                    '[JSON] JoinConversationByCode
                                                                  :> MultiVerb
                                                                       'POST
                                                                       '[JSON]
                                                                       ConvJoinResponses
                                                                       (UpdateResult
                                                                          Event))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "code-check"
        (Summary "Check validity of a conversation code."
         :> (Description
               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
             :> (CanThrow 'CodeNotFound
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'InvalidConversationPassword
                         :> ("conversations"
                             :> ("code-check"
                                 :> (ReqBody '[JSON] ConversationCode
                                     :> MultiVerb
                                          'POST '[JSON] '[RespondEmpty 200 "Valid"] ()))))))))
      :<|> (Named
              "create-conversation-code-unqualified@v3"
              (Summary "Create or recreate a conversation code"
               :> (Until 'V4
                   :> (DescriptionOAuthScope 'WriteConversationsCode
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'CreateConversationCodeConflict
                                       :> (ZUser
                                           :> (ZHostOpt
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> CreateConversationCodeVerb)))))))))))))
            :<|> (Named
                    "create-conversation-code-unqualified"
                    (Summary "Create or recreate a conversation code"
                     :> (From 'V4
                         :> (DescriptionOAuthScope 'WriteConversationsCode
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'CreateConversationCodeConflict
                                             :> (ZUser
                                                 :> (ZHostOpt
                                                     :> (ZOptConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           CreateConversationCodeRequest
                                                                         :> CreateConversationCodeVerb))))))))))))))
                  :<|> (Named
                          "get-conversation-guest-links-status"
                          (Summary
                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'ConvNotFound
                                   :> (ZUser
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               GuestLinksConfig)))))))))
                        :<|> (Named
                                "remove-code-unqualified"
                                (Summary "Delete conversation code"
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("code"
                                                             :> MultiVerb
                                                                  'DELETE
                                                                  '[JSON]
                                                                  '[Respond
                                                                      200
                                                                      "Conversation code deleted."
                                                                      Event]
                                                                  Event))))))))
                              :<|> (Named
                                      "get-code"
                                      (Summary "Get existing conversation code"
                                       :> (CanThrow 'CodeNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'GuestLinksDisabled
                                                       :> (ZHostOpt
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[Respond
                                                                                    200
                                                                                    "Conversation Code"
                                                                                    ConversationCodeInfo]
                                                                                ConversationCodeInfo))))))))))
                                    :<|> (Named
                                            "member-typing-unqualified"
                                            (Summary "Sending typing notifications"
                                             :> (Until 'V3
                                                 :> (MakesFederatedCall
                                                       'Galley "update-typing-indicator"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-typing-indicator-updated"
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("typing"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       TypingStatus
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Notification sent"]
                                                                                          ())))))))))))
                                          :<|> (Named
                                                  "member-typing-qualified"
                                                  (Summary "Sending typing notifications"
                                                   :> (MakesFederatedCall
                                                         'Galley "update-typing-indicator"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-typing-indicator-updated"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("typing"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         TypingStatus
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "Notification sent"]
                                                                                            ()))))))))))
                                                :<|> (Named
                                                        "remove-member-unqualified"
                                                        (Summary
                                                           "Remove a member from a conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "leave-conversation"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (Until 'V2
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Target User ID"]
                                                                                                                   "usr"
                                                                                                                   UserId
                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                      :<|> (Named
                                                              "remove-member"
                                                              (Summary
                                                                 "Remove a member from a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley "leave-conversation"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'RemoveConversationMember)
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("members"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Target User ID"]
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                            :<|> (Named
                                                                    "update-other-member-unqualified"
                                                                    (Summary
                                                                       "Update membership of the specified user (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'ConvMemberNotFound
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyOtherConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidTarget
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("members"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Target User ID"]
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           OtherMemberUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              '[RespondEmpty
                                                                                                                                                  200
                                                                                                                                                  "Membership updated"]
                                                                                                                                              ()))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-other-member"
                                                                          (Summary
                                                                             "Update membership of the specified user"
                                                                           :> (Description
                                                                                 "**Note**: at least one field has to be provided."
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvMemberNotFound
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyOtherConversationMember)
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidTarget
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("members"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Target User ID"]
                                                                                                                                         "usr"
                                                                                                                                         UserId
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             OtherMemberUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Membership updated"]
                                                                                                                                                ())))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name-deprecated"
                                                                                (Summary
                                                                                   "Update conversation name (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationName)
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationRename
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Name unchanged"
                                                                                                                                             "Name updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event)))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name-unqualified"
                                                                                      (Summary
                                                                                         "Update conversation name (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationName)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("name"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationRename
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Name unchanged"
                                                                                                                                                       "Name updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name"
                                                                                            (Summary
                                                                                               "Update conversation name"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationName)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("name"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               ConversationRename
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  (UpdateResponses
                                                                                                                                                     "Name updated"
                                                                                                                                                     "Name unchanged"
                                                                                                                                                     Event)
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                  (Summary
                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("message-timer"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                       Event)
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-message-timer"
                                                                                                        (Summary
                                                                                                           "Update the message timer for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("message-timer"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "update-conversation"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                    (Summary
                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "update-conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (Description
                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                 'V2
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access@v2"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (From
                                                                                                                                                         'V3
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("self"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Maybe
                                                                                                                                                                         Member)))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("self"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                            ()))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-self"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update self membership properties"
                                                                                                                                                         :> (Description
                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                              ())))))))))
                                                                                                                                                      :<|> Named
                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                             (Summary
                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                              :> (From
                                                                                                                                                                    'V5
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "join-conversation-by-code-unqualified"
        (Summary "Join a conversation using a reusable code"
         :> (Description
               "If the guest links team feature is disabled, this will fail with 409 GuestLinksDisabled.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/code-check` which responds with 404 CodeNotFound if guest links are disabled."
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (CanThrow 'CodeNotFound
                     :> (CanThrow 'InvalidConversationPassword
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'GuestLinksDisabled
                                     :> (CanThrow 'InvalidOperation
                                         :> (CanThrow 'NotATeamMember
                                             :> (CanThrow 'TooManyMembers
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> ("join"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       JoinConversationByCode
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          ConvJoinResponses
                                                                          (UpdateResult
                                                                             Event)))))))))))))))))
      :<|> (Named
              "code-check"
              (Summary "Check validity of a conversation code."
               :> (Description
                     "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                   :> (CanThrow 'CodeNotFound
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'InvalidConversationPassword
                               :> ("conversations"
                                   :> ("code-check"
                                       :> (ReqBody '[JSON] ConversationCode
                                           :> MultiVerb
                                                'POST '[JSON] '[RespondEmpty 200 "Valid"] ()))))))))
            :<|> (Named
                    "create-conversation-code-unqualified@v3"
                    (Summary "Create or recreate a conversation code"
                     :> (Until 'V4
                         :> (DescriptionOAuthScope 'WriteConversationsCode
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'CreateConversationCodeConflict
                                             :> (ZUser
                                                 :> (ZHostOpt
                                                     :> (ZOptConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> CreateConversationCodeVerb)))))))))))))
                  :<|> (Named
                          "create-conversation-code-unqualified"
                          (Summary "Create or recreate a conversation code"
                           :> (From 'V4
                               :> (DescriptionOAuthScope 'WriteConversationsCode
                                   :> (CanThrow 'ConvAccessDenied
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'GuestLinksDisabled
                                               :> (CanThrow 'CreateConversationCodeConflict
                                                   :> (ZUser
                                                       :> (ZHostOpt
                                                           :> (ZOptConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 CreateConversationCodeRequest
                                                                               :> CreateConversationCodeVerb))))))))))))))
                        :<|> (Named
                                "get-conversation-guest-links-status"
                                (Summary
                                   "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZUser
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("features"
                                                         :> ("conversationGuestLinks"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     GuestLinksConfig)))))))))
                              :<|> (Named
                                      "remove-code-unqualified"
                                      (Summary "Delete conversation code"
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("code"
                                                                   :> MultiVerb
                                                                        'DELETE
                                                                        '[JSON]
                                                                        '[Respond
                                                                            200
                                                                            "Conversation code deleted."
                                                                            Event]
                                                                        Event))))))))
                                    :<|> (Named
                                            "get-code"
                                            (Summary "Get existing conversation code"
                                             :> (CanThrow 'CodeNotFound
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'GuestLinksDisabled
                                                             :> (ZHostOpt
                                                                 :> (ZLocalUser
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("code"
                                                                                 :> MultiVerb
                                                                                      'GET
                                                                                      '[JSON]
                                                                                      '[Respond
                                                                                          200
                                                                                          "Conversation Code"
                                                                                          ConversationCodeInfo]
                                                                                      ConversationCodeInfo))))))))))
                                          :<|> (Named
                                                  "member-typing-unqualified"
                                                  (Summary "Sending typing notifications"
                                                   :> (Until 'V3
                                                       :> (MakesFederatedCall
                                                             'Galley "update-typing-indicator"
                                                           :> (MakesFederatedCall
                                                                 'Galley
                                                                 "on-typing-indicator-updated"
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("typing"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             TypingStatus
                                                                                           :> MultiVerb
                                                                                                'POST
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Notification sent"]
                                                                                                ())))))))))))
                                                :<|> (Named
                                                        "member-typing-qualified"
                                                        (Summary "Sending typing notifications"
                                                         :> (MakesFederatedCall
                                                               'Galley "update-typing-indicator"
                                                             :> (MakesFederatedCall
                                                                   'Galley
                                                                   "on-typing-indicator-updated"
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("typing"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               TypingStatus
                                                                                             :> MultiVerb
                                                                                                  'POST
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "Notification sent"]
                                                                                                  ()))))))))))
                                                      :<|> (Named
                                                              "remove-member-unqualified"
                                                              (Summary
                                                                 "Remove a member from a conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley "leave-conversation"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (Until 'V2
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("members"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Target User ID"]
                                                                                                                         "usr"
                                                                                                                         UserId
                                                                                                                       :> RemoveFromConversationVerb)))))))))))))))
                                                            :<|> (Named
                                                                    "remove-member"
                                                                    (Summary
                                                                       "Remove a member from a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "leave-conversation"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'RemoveConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("members"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Target User ID"]
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> RemoveFromConversationVerb))))))))))))))
                                                                  :<|> (Named
                                                                          "update-other-member-unqualified"
                                                                          (Summary
                                                                             "Update membership of the specified user (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'ConvMemberNotFound
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyOtherConversationMember)
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidTarget
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("members"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Target User ID"]
                                                                                                                                             "usr"
                                                                                                                                             UserId
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 OtherMemberUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[RespondEmpty
                                                                                                                                                        200
                                                                                                                                                        "Membership updated"]
                                                                                                                                                    ()))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-other-member"
                                                                                (Summary
                                                                                   "Update membership of the specified user"
                                                                                 :> (Description
                                                                                       "**Note**: at least one field has to be provided."
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-conversation-updated"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-mls-message-sent"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'ConvMemberNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyOtherConversationMember)
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidTarget
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("members"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Target User ID"]
                                                                                                                                               "usr"
                                                                                                                                               UserId
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   OtherMemberUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      '[RespondEmpty
                                                                                                                                                          200
                                                                                                                                                          "Membership updated"]
                                                                                                                                                      ())))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name-deprecated"
                                                                                      (Summary
                                                                                         "Update conversation name (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationName)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationRename
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Name unchanged"
                                                                                                                                                   "Name updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name-unqualified"
                                                                                            (Summary
                                                                                               "Update conversation name (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationName)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("name"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationRename
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Name unchanged"
                                                                                                                                                             "Name updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-name"
                                                                                                  (Summary
                                                                                                     "Update conversation name"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationName)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("name"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConversationRename
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        (UpdateResponses
                                                                                                                                                           "Name updated"
                                                                                                                                                           "Name unchanged"
                                                                                                                                                           Event)
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-message-timer-unqualified"
                                                                                                        (Summary
                                                                                                           "Update the message timer for a conversation (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Brig
                                                                                                                               "get-users-by-ids"
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'ModifyConversationMessageTimer)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("message-timer"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                             "Message timer unchanged"
                                                                                                                                                                             "Message timer updated"
                                                                                                                                                                             Event)
                                                                                                                                                                          (UpdateResult
                                                                                                                                                                             Event)))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-message-timer"
                                                                                                              (Summary
                                                                                                                 "Update the message timer for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("message-timer"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                                           "Message timer updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-receipt-mode-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "on-conversation-updated"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-mls-message-sent"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "update-conversation"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (Capture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-receipt-mode"
                                                                                                                          (Summary
                                                                                                                             "Update receipt mode for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Galley
                                                                                                                                         "update-conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Brig
                                                                                                                                             "get-users-by-ids"
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       ('ActionDenied
                                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'ConvNotFound
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                                         :> (Capture'
                                                                                                                                                                                               '[Description
                                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                                               "cnv"
                                                                                                                                                                                               ConvId
                                                                                                                                                                                             :> ("access"
                                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                                       'V2
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                                          'PUT
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                                             Event)
                                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                                             Event)))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access@v2"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V3
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-access"
                                                                                                                                            (Summary
                                                                                                                                               "Update access modes for a conversation"
                                                                                                                                             :> (MakesFederatedCall
                                                                                                                                                   'Galley
                                                                                                                                                   "on-conversation-updated"
                                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                                       'Galley
                                                                                                                                                       "on-mls-message-sent"
                                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                                           'Brig
                                                                                                                                                           "get-users-by-ids"
                                                                                                                                                         :> (From
                                                                                                                                                               'V3
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> (ZConn
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           ('ActionDenied
                                                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               ('ActionDenied
                                                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           'InvalidOperation
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                                                       '[Description
                                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                                       "cnv"
                                                                                                                                                                                                       ConvId
                                                                                                                                                                                                     :> ("access"
                                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                                                     Event)
                                                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                                                     Event))))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-conversation-self-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Get self membership properties (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("self"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (Maybe
                                                                                                                                                                               Member)))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-self-unqualified"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update self membership properties (deprecated)"
                                                                                                                                                         :> (Deprecated
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvNotFound
                                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                                         :> (ZConn
                                                                                                                                                                             :> ("conversations"
                                                                                                                                                                                 :> (Capture'
                                                                                                                                                                                       '[Description
                                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                                       "cnv"
                                                                                                                                                                                       ConvId
                                                                                                                                                                                     :> ("self"
                                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               MemberUpdate
                                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                                  'PUT
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                                      200
                                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                                  ()))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "update-conversation-self"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Update self membership properties"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                                           :> (ZConn
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("self"
                                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 MemberUpdate
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                                                        200
                                                                                                                                                                                                        "Update successful"]
                                                                                                                                                                                                    ())))))))))
                                                                                                                                                            :<|> Named
                                                                                                                                                                   "update-conversation-protocol"
                                                                                                                                                                   (Summary
                                                                                                                                                                      "Update the protocol of the conversation"
                                                                                                                                                                    :> (From
                                                                                                                                                                          'V5
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'ConvNotFound
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          ('ActionDenied
                                                                                                                                                                                             'LeaveConversation)
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'InvalidOperation
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                                                                :> (ZConn
                                                                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                                                                              '[Description
                                                                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                                                                              "cnv"
                                                                                                                                                                                                                              ConvId
                                                                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                                                                         'PUT
                                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"code-check" ServerT
  (Summary "Check validity of a conversation code."
   :> (Description
         "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
       :> (CanThrow 'CodeNotFound
           :> (CanThrow 'ConvNotFound
               :> (CanThrow 'InvalidConversationPassword
                   :> ("conversations"
                       :> ("code-check"
                           :> (ReqBody '[JSON] ConversationCode
                               :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "Valid"] ()))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Check validity of a conversation code."
            :> (Description
                  "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
                :> (CanThrow 'CodeNotFound
                    :> (CanThrow 'ConvNotFound
                        :> (CanThrow 'InvalidConversationPassword
                            :> ("conversations"
                                :> ("code-check"
                                    :> (ReqBody '[JSON] ConversationCode
                                        :> MultiVerb
                                             'POST '[JSON] '[RespondEmpty 200 "Valid"] ())))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
ConversationCode
-> Sem
     '[Error (Tagged 'CodeNotFound ()), Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidConversationPassword ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member CodeStore r, Member ConversationStore r,
 Member TeamFeatureStore r,
 Member (Error (Tagged 'CodeNotFound ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidConversationPassword ())) r,
 Member (Input Opts) r) =>
ConversationCode -> Sem r ()
checkReusableCode
    API
  (Named
     "code-check"
     (Summary "Check validity of a conversation code."
      :> (Description
            "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
          :> (CanThrow 'CodeNotFound
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'InvalidConversationPassword
                      :> ("conversations"
                          :> ("code-check"
                              :> (ReqBody '[JSON] ConversationCode
                                  :> MultiVerb 'POST '[JSON] '[RespondEmpty 200 "Valid"] ())))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-conversation-code-unqualified@v3"
        (Summary "Create or recreate a conversation code"
         :> (Until 'V4
             :> (DescriptionOAuthScope 'WriteConversationsCode
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'CreateConversationCodeConflict
                                 :> (ZUser
                                     :> (ZHostOpt
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> CreateConversationCodeVerb)))))))))))))
      :<|> (Named
              "create-conversation-code-unqualified"
              (Summary "Create or recreate a conversation code"
               :> (From 'V4
                   :> (DescriptionOAuthScope 'WriteConversationsCode
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'CreateConversationCodeConflict
                                       :> (ZUser
                                           :> (ZHostOpt
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     CreateConversationCodeRequest
                                                                   :> CreateConversationCodeVerb))))))))))))))
            :<|> (Named
                    "get-conversation-guest-links-status"
                    (Summary
                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'ConvNotFound
                             :> (ZUser
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("features"
                                             :> ("conversationGuestLinks"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature GuestLinksConfig)))))))))
                  :<|> (Named
                          "remove-code-unqualified"
                          (Summary "Delete conversation code"
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'ConvNotFound
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> ("conversations"
                                               :> (Capture'
                                                     '[Description "Conversation ID"] "cnv" ConvId
                                                   :> ("code"
                                                       :> MultiVerb
                                                            'DELETE
                                                            '[JSON]
                                                            '[Respond
                                                                200
                                                                "Conversation code deleted."
                                                                Event]
                                                            Event))))))))
                        :<|> (Named
                                "get-code"
                                (Summary "Get existing conversation code"
                                 :> (CanThrow 'CodeNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'GuestLinksDisabled
                                                 :> (ZHostOpt
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[Respond
                                                                              200
                                                                              "Conversation Code"
                                                                              ConversationCodeInfo]
                                                                          ConversationCodeInfo))))))))))
                              :<|> (Named
                                      "member-typing-unqualified"
                                      (Summary "Sending typing notifications"
                                       :> (Until 'V3
                                           :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                               :> (MakesFederatedCall
                                                     'Galley "on-typing-indicator-updated"
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("typing"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 TypingStatus
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200
                                                                                        "Notification sent"]
                                                                                    ())))))))))))
                                    :<|> (Named
                                            "member-typing-qualified"
                                            (Summary "Sending typing notifications"
                                             :> (MakesFederatedCall
                                                   'Galley "update-typing-indicator"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-typing-indicator-updated"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("typing"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TypingStatus
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "Notification sent"]
                                                                                      ()))))))))))
                                          :<|> (Named
                                                  "remove-member-unqualified"
                                                  (Summary
                                                     "Remove a member from a conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "leave-conversation"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (Until 'V2
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Target User ID"]
                                                                                                             "usr"
                                                                                                             UserId
                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                :<|> (Named
                                                        "remove-member"
                                                        (Summary
                                                           "Remove a member from a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "leave-conversation"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'RemoveConversationMember)
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("members"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Target User ID"]
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                      :<|> (Named
                                                              "update-other-member-unqualified"
                                                              (Summary
                                                                 "Update membership of the specified user (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'ConvMemberNotFound
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyOtherConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             'InvalidTarget
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("members"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Target User ID"]
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     OtherMemberUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        '[RespondEmpty
                                                                                                                                            200
                                                                                                                                            "Membership updated"]
                                                                                                                                        ()))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-other-member"
                                                                    (Summary
                                                                       "Update membership of the specified user"
                                                                     :> (Description
                                                                           "**Note**: at least one field has to be provided."
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvMemberNotFound
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyOtherConversationMember)
                                                                                                         :> (CanThrow
                                                                                                               'InvalidTarget
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("members"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Target User ID"]
                                                                                                                                   "usr"
                                                                                                                                   UserId
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       OtherMemberUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Membership updated"]
                                                                                                                                          ())))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name-deprecated"
                                                                          (Summary
                                                                             "Update conversation name (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationName)
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationRename
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Name unchanged"
                                                                                                                                       "Name updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event)))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name-unqualified"
                                                                                (Summary
                                                                                   "Update conversation name (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationName)
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("name"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationRename
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Name unchanged"
                                                                                                                                                 "Name updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name"
                                                                                      (Summary
                                                                                         "Update conversation name"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationName)
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("name"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         ConversationRename
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            (UpdateResponses
                                                                                                                                               "Name updated"
                                                                                                                                               "Name unchanged"
                                                                                                                                               Event)
                                                                                                                                            (UpdateResult
                                                                                                                                               Event))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-message-timer-unqualified"
                                                                                            (Summary
                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("message-timer"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              (UpdateResponses
                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                 Event)
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-message-timer"
                                                                                                  (Summary
                                                                                                     "Update the message timer for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("message-timer"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                               "Message timer updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                        (Summary
                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "update-conversation"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-receipt-mode"
                                                                                                              (Summary
                                                                                                                 "Update receipt mode for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "update-conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (Description
                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                           'V2
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access@v2"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                             'V2
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (From
                                                                                                                                                   'V3
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("self"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Maybe
                                                                                                                                                                   Member)))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("self"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                      ()))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-self"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update self membership properties"
                                                                                                                                                   :> (Description
                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("self"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                            200
                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                        ())))))))))
                                                                                                                                                :<|> Named
                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                       (Summary
                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                        :> (From
                                                                                                                                                              'V5
                                                                                                                                                            :> (Description
                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "code-check"
        (Summary "Check validity of a conversation code."
         :> (Description
               "If the guest links team feature is disabled, this will fail with 404 CodeNotFound.Note that this is currently inconsistent (for backwards compatibility reasons) with `POST /conversations/join` which responds with 409 GuestLinksDisabled if guest links are disabled."
             :> (CanThrow 'CodeNotFound
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'InvalidConversationPassword
                         :> ("conversations"
                             :> ("code-check"
                                 :> (ReqBody '[JSON] ConversationCode
                                     :> MultiVerb
                                          'POST '[JSON] '[RespondEmpty 200 "Valid"] ()))))))))
      :<|> (Named
              "create-conversation-code-unqualified@v3"
              (Summary "Create or recreate a conversation code"
               :> (Until 'V4
                   :> (DescriptionOAuthScope 'WriteConversationsCode
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'CreateConversationCodeConflict
                                       :> (ZUser
                                           :> (ZHostOpt
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> CreateConversationCodeVerb)))))))))))))
            :<|> (Named
                    "create-conversation-code-unqualified"
                    (Summary "Create or recreate a conversation code"
                     :> (From 'V4
                         :> (DescriptionOAuthScope 'WriteConversationsCode
                             :> (CanThrow 'ConvAccessDenied
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'GuestLinksDisabled
                                         :> (CanThrow 'CreateConversationCodeConflict
                                             :> (ZUser
                                                 :> (ZHostOpt
                                                     :> (ZOptConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           CreateConversationCodeRequest
                                                                         :> CreateConversationCodeVerb))))))))))))))
                  :<|> (Named
                          "get-conversation-guest-links-status"
                          (Summary
                             "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'ConvNotFound
                                   :> (ZUser
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               GuestLinksConfig)))))))))
                        :<|> (Named
                                "remove-code-unqualified"
                                (Summary "Delete conversation code"
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("code"
                                                             :> MultiVerb
                                                                  'DELETE
                                                                  '[JSON]
                                                                  '[Respond
                                                                      200
                                                                      "Conversation code deleted."
                                                                      Event]
                                                                  Event))))))))
                              :<|> (Named
                                      "get-code"
                                      (Summary "Get existing conversation code"
                                       :> (CanThrow 'CodeNotFound
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'GuestLinksDisabled
                                                       :> (ZHostOpt
                                                           :> (ZLocalUser
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("code"
                                                                           :> MultiVerb
                                                                                'GET
                                                                                '[JSON]
                                                                                '[Respond
                                                                                    200
                                                                                    "Conversation Code"
                                                                                    ConversationCodeInfo]
                                                                                ConversationCodeInfo))))))))))
                                    :<|> (Named
                                            "member-typing-unqualified"
                                            (Summary "Sending typing notifications"
                                             :> (Until 'V3
                                                 :> (MakesFederatedCall
                                                       'Galley "update-typing-indicator"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-typing-indicator-updated"
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("typing"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       TypingStatus
                                                                                     :> MultiVerb
                                                                                          'POST
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Notification sent"]
                                                                                          ())))))))))))
                                          :<|> (Named
                                                  "member-typing-qualified"
                                                  (Summary "Sending typing notifications"
                                                   :> (MakesFederatedCall
                                                         'Galley "update-typing-indicator"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-typing-indicator-updated"
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("typing"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         TypingStatus
                                                                                       :> MultiVerb
                                                                                            'POST
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "Notification sent"]
                                                                                            ()))))))))))
                                                :<|> (Named
                                                        "remove-member-unqualified"
                                                        (Summary
                                                           "Remove a member from a conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "leave-conversation"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (Until 'V2
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("members"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Target User ID"]
                                                                                                                   "usr"
                                                                                                                   UserId
                                                                                                                 :> RemoveFromConversationVerb)))))))))))))))
                                                      :<|> (Named
                                                              "remove-member"
                                                              (Summary
                                                                 "Remove a member from a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley "leave-conversation"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'RemoveConversationMember)
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("members"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Target User ID"]
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> RemoveFromConversationVerb))))))))))))))
                                                            :<|> (Named
                                                                    "update-other-member-unqualified"
                                                                    (Summary
                                                                       "Update membership of the specified user (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'ConvMemberNotFound
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyOtherConversationMember)
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidTarget
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("members"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Target User ID"]
                                                                                                                                       "usr"
                                                                                                                                       UserId
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           OtherMemberUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              '[RespondEmpty
                                                                                                                                                  200
                                                                                                                                                  "Membership updated"]
                                                                                                                                              ()))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-other-member"
                                                                          (Summary
                                                                             "Update membership of the specified user"
                                                                           :> (Description
                                                                                 "**Note**: at least one field has to be provided."
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-conversation-updated"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-mls-message-sent"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'ConvMemberNotFound
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyOtherConversationMember)
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidTarget
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("members"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Target User ID"]
                                                                                                                                         "usr"
                                                                                                                                         UserId
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             OtherMemberUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                '[RespondEmpty
                                                                                                                                                    200
                                                                                                                                                    "Membership updated"]
                                                                                                                                                ())))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name-deprecated"
                                                                                (Summary
                                                                                   "Update conversation name (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationName)
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationRename
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Name unchanged"
                                                                                                                                             "Name updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event)))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name-unqualified"
                                                                                      (Summary
                                                                                         "Update conversation name (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/name` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationName)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("name"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationRename
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Name unchanged"
                                                                                                                                                       "Name updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-name"
                                                                                            (Summary
                                                                                               "Update conversation name"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationName)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("name"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               ConversationRename
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  (UpdateResponses
                                                                                                                                                     "Name updated"
                                                                                                                                                     "Name unchanged"
                                                                                                                                                     Event)
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-message-timer-unqualified"
                                                                                                  (Summary
                                                                                                     "Update the message timer for a conversation (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Brig
                                                                                                                         "get-users-by-ids"
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'ModifyConversationMessageTimer)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("message-timer"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                       "Message timer unchanged"
                                                                                                                                                                       "Message timer updated"
                                                                                                                                                                       Event)
                                                                                                                                                                    (UpdateResult
                                                                                                                                                                       Event)))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-message-timer"
                                                                                                        (Summary
                                                                                                           "Update the message timer for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("message-timer"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                                     "Message timer updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-receipt-mode-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update receipt mode for a conversation (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "on-conversation-updated"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-mls-message-sent"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "update-conversation"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (Capture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("receipt-mode"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-receipt-mode"
                                                                                                                    (Summary
                                                                                                                       "Update receipt mode for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Galley
                                                                                                                                   "update-conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Brig
                                                                                                                                       "get-users-by-ids"
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidOperation
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation (deprecated)"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (Description
                                                                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 ('ActionDenied
                                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'ConvNotFound
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidOperation
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                                               :> ("conversations"
                                                                                                                                                                                   :> (Capture'
                                                                                                                                                                                         '[Description
                                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                                         "cnv"
                                                                                                                                                                                         ConvId
                                                                                                                                                                                       :> ("access"
                                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                                 'V2
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                                    'PUT
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                                       Event)
                                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                                       Event)))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access@v2"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (Until
                                                                                                                                                   'V3
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-access"
                                                                                                                                      (Summary
                                                                                                                                         "Update access modes for a conversation"
                                                                                                                                       :> (MakesFederatedCall
                                                                                                                                             'Galley
                                                                                                                                             "on-conversation-updated"
                                                                                                                                           :> (MakesFederatedCall
                                                                                                                                                 'Galley
                                                                                                                                                 "on-mls-message-sent"
                                                                                                                                               :> (MakesFederatedCall
                                                                                                                                                     'Brig
                                                                                                                                                     "get-users-by-ids"
                                                                                                                                                   :> (From
                                                                                                                                                         'V3
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> (ZConn
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     ('ActionDenied
                                                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         ('ActionDenied
                                                                                                                                                                            'RemoveConversationMember)
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'ConvAccessDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'ConvNotFound
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     'InvalidOperation
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                                                 '[Description
                                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                                 "cnv"
                                                                                                                                                                                                 ConvId
                                                                                                                                                                                               :> ("access"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                                            'PUT
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                                                               "Access updated"
                                                                                                                                                                                                               Event)
                                                                                                                                                                                                            (UpdateResult
                                                                                                                                                                                                               Event))))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-conversation-self-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Get self membership properties (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("self"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (Maybe
                                                                                                                                                                         Member)))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-self-unqualified"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update self membership properties (deprecated)"
                                                                                                                                                   :> (Deprecated
                                                                                                                                                       :> (Description
                                                                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvNotFound
                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                   :> (ZConn
                                                                                                                                                                       :> ("conversations"
                                                                                                                                                                           :> (Capture'
                                                                                                                                                                                 '[Description
                                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                                 "cnv"
                                                                                                                                                                                 ConvId
                                                                                                                                                                               :> ("self"
                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         MemberUpdate
                                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                                            'PUT
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                                200
                                                                                                                                                                                                "Update successful"]
                                                                                                                                                                                            ()))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "update-conversation-self"
                                                                                                                                                        (Summary
                                                                                                                                                           "Update self membership properties"
                                                                                                                                                         :> (Description
                                                                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                                     :> (ZConn
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("self"
                                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           MemberUpdate
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                                                  200
                                                                                                                                                                                                  "Update successful"]
                                                                                                                                                                                              ())))))))))
                                                                                                                                                      :<|> Named
                                                                                                                                                             "update-conversation-protocol"
                                                                                                                                                             (Summary
                                                                                                                                                                "Update the protocol of the conversation"
                                                                                                                                                              :> (From
                                                                                                                                                                    'V5
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'ConvNotFound
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    ('ActionDenied
                                                                                                                                                                                       'LeaveConversation)
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'InvalidOperation
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                                                                          :> (ZConn
                                                                                                                                                                                                              :> ("conversations"
                                                                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                                                                        '[Description
                                                                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                                                                        "cnv"
                                                                                                                                                                                                                        ConvId
                                                                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                                                                   'PUT
                                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-conversation-code-unqualified@v3" (Maybe CreateConversationCodeRequest
-> UserId
-> Maybe Text
-> Maybe ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'CreateConversationCodeConflict ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     AddCodeResult
forall (r :: EffectRow).
(Member CodeStore r, Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'GuestLinksDisabled ())) r,
 Member (Error (Tagged 'CreateConversationCodeConflict ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input (Local ())) r, Member (Input UTCTime) r,
 Member (Input Opts) r, Member (Embed IO) r,
 Member TeamFeatureStore r) =>
Maybe CreateConversationCodeRequest
-> UserId
-> Maybe Text
-> Maybe ConnId
-> ConvId
-> Sem r AddCodeResult
addCodeUnqualified Maybe CreateConversationCodeRequest
forall a. Maybe a
Nothing)
    API
  (Named
     "create-conversation-code-unqualified@v3"
     (Summary "Create or recreate a conversation code"
      :> (Until 'V4
          :> (DescriptionOAuthScope 'WriteConversationsCode
              :> (CanThrow 'ConvAccessDenied
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'GuestLinksDisabled
                          :> (CanThrow 'CreateConversationCodeConflict
                              :> (ZUser
                                  :> (ZHostOpt
                                      :> (ZOptConn
                                          :> ("conversations"
                                              :> (Capture'
                                                    '[Description "Conversation ID"] "cnv" ConvId
                                                  :> ("code"
                                                      :> CreateConversationCodeVerb))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "create-conversation-code-unqualified"
        (Summary "Create or recreate a conversation code"
         :> (From 'V4
             :> (DescriptionOAuthScope 'WriteConversationsCode
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'CreateConversationCodeConflict
                                 :> (ZUser
                                     :> (ZHostOpt
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> (ReqBody
                                                               '[JSON] CreateConversationCodeRequest
                                                             :> CreateConversationCodeVerb))))))))))))))
      :<|> (Named
              "get-conversation-guest-links-status"
              (Summary
                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
               :> (CanThrow 'ConvAccessDenied
                   :> (CanThrow 'ConvNotFound
                       :> (ZUser
                           :> ("conversations"
                               :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                   :> ("features"
                                       :> ("conversationGuestLinks"
                                           :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))
            :<|> (Named
                    "remove-code-unqualified"
                    (Summary "Delete conversation code"
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'ConvNotFound
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> ("conversations"
                                         :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                             :> ("code"
                                                 :> MultiVerb
                                                      'DELETE
                                                      '[JSON]
                                                      '[Respond
                                                          200 "Conversation code deleted." Event]
                                                      Event))))))))
                  :<|> (Named
                          "get-code"
                          (Summary "Get existing conversation code"
                           :> (CanThrow 'CodeNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'GuestLinksDisabled
                                           :> (ZHostOpt
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[Respond
                                                                        200
                                                                        "Conversation Code"
                                                                        ConversationCodeInfo]
                                                                    ConversationCodeInfo))))))))))
                        :<|> (Named
                                "member-typing-unqualified"
                                (Summary "Sending typing notifications"
                                 :> (Until 'V3
                                     :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                         :> (MakesFederatedCall
                                               'Galley "on-typing-indicator-updated"
                                             :> (CanThrow 'ConvNotFound
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("typing"
                                                                     :> (ReqBody
                                                                           '[JSON] TypingStatus
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200
                                                                                  "Notification sent"]
                                                                              ())))))))))))
                              :<|> (Named
                                      "member-typing-qualified"
                                      (Summary "Sending typing notifications"
                                       :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                           :> (MakesFederatedCall
                                                 'Galley "on-typing-indicator-updated"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("typing"
                                                                       :> (ReqBody
                                                                             '[JSON] TypingStatus
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "Notification sent"]
                                                                                ()))))))))))
                                    :<|> (Named
                                            "remove-member-unqualified"
                                            (Summary
                                               "Remove a member from a conversation (deprecated)"
                                             :> (MakesFederatedCall 'Galley "leave-conversation"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (Until 'V2
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Target User ID"]
                                                                                                       "usr"
                                                                                                       UserId
                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                          :<|> (Named
                                                  "remove-member"
                                                  (Summary "Remove a member from a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "leave-conversation"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'RemoveConversationMember)
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("members"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Target User ID"]
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                :<|> (Named
                                                        "update-other-member-unqualified"
                                                        (Summary
                                                           "Update membership of the specified user (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'ConvMemberNotFound
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyOtherConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       'InvalidTarget
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("members"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Target User ID"]
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               OtherMemberUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  '[RespondEmpty
                                                                                                                                      200
                                                                                                                                      "Membership updated"]
                                                                                                                                  ()))))))))))))))))))
                                                      :<|> (Named
                                                              "update-other-member"
                                                              (Summary
                                                                 "Update membership of the specified user"
                                                               :> (Description
                                                                     "**Note**: at least one field has to be provided."
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvMemberNotFound
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyOtherConversationMember)
                                                                                                   :> (CanThrow
                                                                                                         'InvalidTarget
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("members"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Target User ID"]
                                                                                                                             "usr"
                                                                                                                             UserId
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 OtherMemberUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Membership updated"]
                                                                                                                                    ())))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name-deprecated"
                                                                    (Summary
                                                                       "Update conversation name (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationName)
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationRename
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Name unchanged"
                                                                                                                                 "Name updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event)))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name-unqualified"
                                                                          (Summary
                                                                             "Update conversation name (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationName)
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("name"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationRename
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Name unchanged"
                                                                                                                                           "Name updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name"
                                                                                (Summary
                                                                                   "Update conversation name"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationName)
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("name"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   ConversationRename
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      (UpdateResponses
                                                                                                                                         "Name updated"
                                                                                                                                         "Name unchanged"
                                                                                                                                         Event)
                                                                                                                                      (UpdateResult
                                                                                                                                         Event))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-message-timer-unqualified"
                                                                                      (Summary
                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("message-timer"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        (UpdateResponses
                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                           "Message timer updated"
                                                                                                                                                           Event)
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-message-timer"
                                                                                            (Summary
                                                                                               "Update the message timer for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("message-timer"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                         "Message timer updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                  (Summary
                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "update-conversation"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-receipt-mode"
                                                                                                        (Summary
                                                                                                           "Update receipt mode for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "update-conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (Description
                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("access"
                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                     'V2
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access@v2"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("access"
                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                       'V2
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (From
                                                                                                                                             'V3
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Maybe
                                                                                                                                                             Member)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("self"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             MemberUpdate
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                ()))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-self"
                                                                                                                                            (Summary
                                                                                                                                               "Update self membership properties"
                                                                                                                                             :> (Description
                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("self"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               MemberUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                      200
                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                  ())))))))))
                                                                                                                                          :<|> Named
                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                 (Summary
                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                  :> (From
                                                                                                                                                        'V5
                                                                                                                                                      :> (Description
                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'ConvNotFound
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-conversation-code-unqualified@v3"
        (Summary "Create or recreate a conversation code"
         :> (Until 'V4
             :> (DescriptionOAuthScope 'WriteConversationsCode
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'CreateConversationCodeConflict
                                 :> (ZUser
                                     :> (ZHostOpt
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> CreateConversationCodeVerb)))))))))))))
      :<|> (Named
              "create-conversation-code-unqualified"
              (Summary "Create or recreate a conversation code"
               :> (From 'V4
                   :> (DescriptionOAuthScope 'WriteConversationsCode
                       :> (CanThrow 'ConvAccessDenied
                           :> (CanThrow 'ConvNotFound
                               :> (CanThrow 'GuestLinksDisabled
                                   :> (CanThrow 'CreateConversationCodeConflict
                                       :> (ZUser
                                           :> (ZHostOpt
                                               :> (ZOptConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     CreateConversationCodeRequest
                                                                   :> CreateConversationCodeVerb))))))))))))))
            :<|> (Named
                    "get-conversation-guest-links-status"
                    (Summary
                       "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'ConvNotFound
                             :> (ZUser
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("features"
                                             :> ("conversationGuestLinks"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature GuestLinksConfig)))))))))
                  :<|> (Named
                          "remove-code-unqualified"
                          (Summary "Delete conversation code"
                           :> (CanThrow 'ConvAccessDenied
                               :> (CanThrow 'ConvNotFound
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> ("conversations"
                                               :> (Capture'
                                                     '[Description "Conversation ID"] "cnv" ConvId
                                                   :> ("code"
                                                       :> MultiVerb
                                                            'DELETE
                                                            '[JSON]
                                                            '[Respond
                                                                200
                                                                "Conversation code deleted."
                                                                Event]
                                                            Event))))))))
                        :<|> (Named
                                "get-code"
                                (Summary "Get existing conversation code"
                                 :> (CanThrow 'CodeNotFound
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'GuestLinksDisabled
                                                 :> (ZHostOpt
                                                     :> (ZLocalUser
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("code"
                                                                     :> MultiVerb
                                                                          'GET
                                                                          '[JSON]
                                                                          '[Respond
                                                                              200
                                                                              "Conversation Code"
                                                                              ConversationCodeInfo]
                                                                          ConversationCodeInfo))))))))))
                              :<|> (Named
                                      "member-typing-unqualified"
                                      (Summary "Sending typing notifications"
                                       :> (Until 'V3
                                           :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                               :> (MakesFederatedCall
                                                     'Galley "on-typing-indicator-updated"
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("typing"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 TypingStatus
                                                                               :> MultiVerb
                                                                                    'POST
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200
                                                                                        "Notification sent"]
                                                                                    ())))))))))))
                                    :<|> (Named
                                            "member-typing-qualified"
                                            (Summary "Sending typing notifications"
                                             :> (MakesFederatedCall
                                                   'Galley "update-typing-indicator"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-typing-indicator-updated"
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("typing"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   TypingStatus
                                                                                 :> MultiVerb
                                                                                      'POST
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "Notification sent"]
                                                                                      ()))))))))))
                                          :<|> (Named
                                                  "remove-member-unqualified"
                                                  (Summary
                                                     "Remove a member from a conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "leave-conversation"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (Until 'V2
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("members"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Target User ID"]
                                                                                                             "usr"
                                                                                                             UserId
                                                                                                           :> RemoveFromConversationVerb)))))))))))))))
                                                :<|> (Named
                                                        "remove-member"
                                                        (Summary
                                                           "Remove a member from a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "leave-conversation"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'RemoveConversationMember)
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("members"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Target User ID"]
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> RemoveFromConversationVerb))))))))))))))
                                                      :<|> (Named
                                                              "update-other-member-unqualified"
                                                              (Summary
                                                                 "Update membership of the specified user (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'ConvMemberNotFound
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyOtherConversationMember)
                                                                                                       :> (CanThrow
                                                                                                             'InvalidTarget
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("members"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Target User ID"]
                                                                                                                                 "usr"
                                                                                                                                 UserId
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     OtherMemberUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        '[RespondEmpty
                                                                                                                                            200
                                                                                                                                            "Membership updated"]
                                                                                                                                        ()))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-other-member"
                                                                    (Summary
                                                                       "Update membership of the specified user"
                                                                     :> (Description
                                                                           "**Note**: at least one field has to be provided."
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-conversation-updated"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-mls-message-sent"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'ConvMemberNotFound
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyOtherConversationMember)
                                                                                                         :> (CanThrow
                                                                                                               'InvalidTarget
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("members"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Target User ID"]
                                                                                                                                   "usr"
                                                                                                                                   UserId
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       OtherMemberUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          '[RespondEmpty
                                                                                                                                              200
                                                                                                                                              "Membership updated"]
                                                                                                                                          ())))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name-deprecated"
                                                                          (Summary
                                                                             "Update conversation name (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationName)
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationRename
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Name unchanged"
                                                                                                                                       "Name updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event)))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name-unqualified"
                                                                                (Summary
                                                                                   "Update conversation name (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/name` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationName)
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("name"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationRename
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Name unchanged"
                                                                                                                                                 "Name updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-name"
                                                                                      (Summary
                                                                                         "Update conversation name"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationName)
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (QualifiedCapture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("name"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         ConversationRename
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            (UpdateResponses
                                                                                                                                               "Name updated"
                                                                                                                                               "Name unchanged"
                                                                                                                                               Event)
                                                                                                                                            (UpdateResult
                                                                                                                                               Event))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-message-timer-unqualified"
                                                                                            (Summary
                                                                                               "Update the message timer for a conversation (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Brig
                                                                                                                   "get-users-by-ids"
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'ModifyConversationMessageTimer)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("message-timer"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              (UpdateResponses
                                                                                                                                                                 "Message timer unchanged"
                                                                                                                                                                 "Message timer updated"
                                                                                                                                                                 Event)
                                                                                                                                                              (UpdateResult
                                                                                                                                                                 Event)))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-message-timer"
                                                                                                  (Summary
                                                                                                     "Update the message timer for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationMessageTimer)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("message-timer"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Message timer unchanged"
                                                                                                                                                               "Message timer updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-receipt-mode-unqualified"
                                                                                                        (Summary
                                                                                                           "Update receipt mode for a conversation (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "on-conversation-updated"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-mls-message-sent"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "update-conversation"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (Capture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("receipt-mode"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-receipt-mode"
                                                                                                              (Summary
                                                                                                                 "Update receipt mode for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Galley
                                                                                                                             "update-conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Brig
                                                                                                                                 "get-users-by-ids"
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvAccessDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidOperation
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation (deprecated)"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (Description
                                                                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           ('ActionDenied
                                                                                                                                                              'RemoveConversationMember)
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvAccessDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'ConvNotFound
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidOperation
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                                         :> ("conversations"
                                                                                                                                                                             :> (Capture'
                                                                                                                                                                                   '[Description
                                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                                   "cnv"
                                                                                                                                                                                   ConvId
                                                                                                                                                                                 :> ("access"
                                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                                           'V2
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                                              'PUT
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                                 Event)
                                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                                 Event)))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access@v2"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (Until
                                                                                                                                             'V3
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                                                             'V2
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-access"
                                                                                                                                (Summary
                                                                                                                                   "Update access modes for a conversation"
                                                                                                                                 :> (MakesFederatedCall
                                                                                                                                       'Galley
                                                                                                                                       "on-conversation-updated"
                                                                                                                                     :> (MakesFederatedCall
                                                                                                                                           'Galley
                                                                                                                                           "on-mls-message-sent"
                                                                                                                                         :> (MakesFederatedCall
                                                                                                                                               'Brig
                                                                                                                                               "get-users-by-ids"
                                                                                                                                             :> (From
                                                                                                                                                   'V3
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> (ZConn
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               ('ActionDenied
                                                                                                                                                                  'ModifyConversationAccess)
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   ('ActionDenied
                                                                                                                                                                      'RemoveConversationMember)
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'ConvAccessDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'ConvNotFound
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               'InvalidOperation
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                                                           '[Description
                                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                                           "cnv"
                                                                                                                                                                                           ConvId
                                                                                                                                                                                         :> ("access"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                                      'PUT
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                                                         "Access updated"
                                                                                                                                                                                                         Event)
                                                                                                                                                                                                      (UpdateResult
                                                                                                                                                                                                         Event))))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-conversation-self-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Get self membership properties (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("self"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (Maybe
                                                                                                                                                                   Member)))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-self-unqualified"
                                                                                                                                            (Summary
                                                                                                                                               "Update self membership properties (deprecated)"
                                                                                                                                             :> (Deprecated
                                                                                                                                                 :> (Description
                                                                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvNotFound
                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                             :> (ZConn
                                                                                                                                                                 :> ("conversations"
                                                                                                                                                                     :> (Capture'
                                                                                                                                                                           '[Description
                                                                                                                                                                               "Conversation ID"]
                                                                                                                                                                           "cnv"
                                                                                                                                                                           ConvId
                                                                                                                                                                         :> ("self"
                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   MemberUpdate
                                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                                      'PUT
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                                          200
                                                                                                                                                                                          "Update successful"]
                                                                                                                                                                                      ()))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "update-conversation-self"
                                                                                                                                                  (Summary
                                                                                                                                                     "Update self membership properties"
                                                                                                                                                   :> (Description
                                                                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (ZLocalUser
                                                                                                                                                               :> (ZConn
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("self"
                                                                                                                                                                               :> (ReqBody
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     MemberUpdate
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        '[RespondEmpty
                                                                                                                                                                                            200
                                                                                                                                                                                            "Update successful"]
                                                                                                                                                                                        ())))))))))
                                                                                                                                                :<|> Named
                                                                                                                                                       "update-conversation-protocol"
                                                                                                                                                       (Summary
                                                                                                                                                          "Update the protocol of the conversation"
                                                                                                                                                        :> (From
                                                                                                                                                              'V5
                                                                                                                                                            :> (Description
                                                                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'ConvNotFound
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              ('ActionDenied
                                                                                                                                                                                 'LeaveConversation)
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'InvalidOperation
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                :> (ZLocalUser
                                                                                                                                                                                                    :> (ZConn
                                                                                                                                                                                                        :> ("conversations"
                                                                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                                                                  '[Description
                                                                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                                                                  "cnv"
                                                                                                                                                                                                                  ConvId
                                                                                                                                                                                                                :> ("protocol"
                                                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                                                                             'PUT
                                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"create-conversation-code-unqualified" ServerT
  (Summary "Create or recreate a conversation code"
   :> (From 'V4
       :> (DescriptionOAuthScope 'WriteConversationsCode
           :> (CanThrow 'ConvAccessDenied
               :> (CanThrow 'ConvNotFound
                   :> (CanThrow 'GuestLinksDisabled
                       :> (CanThrow 'CreateConversationCodeConflict
                           :> (ZUser
                               :> (ZHostOpt
                                   :> (ZOptConn
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("code"
                                                   :> (ReqBody '[JSON] CreateConversationCodeRequest
                                                       :> CreateConversationCodeVerb))))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Create or recreate a conversation code"
            :> (From 'V4
                :> (DescriptionOAuthScope 'WriteConversationsCode
                    :> (CanThrow 'ConvAccessDenied
                        :> (CanThrow 'ConvNotFound
                            :> (CanThrow 'GuestLinksDisabled
                                :> (CanThrow 'CreateConversationCodeConflict
                                    :> (ZUser
                                        :> (ZHostOpt
                                            :> (ZOptConn
                                                :> ("conversations"
                                                    :> (Capture'
                                                          '[Description "Conversation ID"]
                                                          "cnv"
                                                          ConvId
                                                        :> ("code"
                                                            :> (ReqBody
                                                                  '[JSON]
                                                                  CreateConversationCodeRequest
                                                                :> CreateConversationCodeVerb)))))))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
UserId
-> Maybe Text
-> Maybe ConnId
-> ConvId
-> CreateConversationCodeRequest
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()),
       Error (Tagged 'CreateConversationCodeConflict ()), BrigAccess,
       SparAccess, NotificationSubsystem, GundeckAPIAccess, Rpc,
       ExternalAccess, FederatorAccess, BackendNotificationQueueAccess,
       BotAccess, FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     AddCodeResult
forall (r :: EffectRow).
(Member CodeStore r, Member ConversationStore r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'GuestLinksDisabled ())) r,
 Member (Error (Tagged 'CreateConversationCodeConflict ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input (Local ())) r, Member (Input UTCTime) r,
 Member (Embed IO) r, Member (Input Opts) r,
 Member TeamFeatureStore r) =>
UserId
-> Maybe Text
-> Maybe ConnId
-> ConvId
-> CreateConversationCodeRequest
-> Sem r AddCodeResult
addCodeUnqualifiedWithReqBody
    API
  (Named
     "create-conversation-code-unqualified"
     (Summary "Create or recreate a conversation code"
      :> (From 'V4
          :> (DescriptionOAuthScope 'WriteConversationsCode
              :> (CanThrow 'ConvAccessDenied
                  :> (CanThrow 'ConvNotFound
                      :> (CanThrow 'GuestLinksDisabled
                          :> (CanThrow 'CreateConversationCodeConflict
                              :> (ZUser
                                  :> (ZHostOpt
                                      :> (ZOptConn
                                          :> ("conversations"
                                              :> (Capture'
                                                    '[Description "Conversation ID"] "cnv" ConvId
                                                  :> ("code"
                                                      :> (ReqBody
                                                            '[JSON] CreateConversationCodeRequest
                                                          :> CreateConversationCodeVerb)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation-guest-links-status"
        (Summary
           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
         :> (CanThrow 'ConvAccessDenied
             :> (CanThrow 'ConvNotFound
                 :> (ZUser
                     :> ("conversations"
                         :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                             :> ("features"
                                 :> ("conversationGuestLinks"
                                     :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))
      :<|> (Named
              "remove-code-unqualified"
              (Summary "Delete conversation code"
               :> (CanThrow 'ConvAccessDenied
                   :> (CanThrow 'ConvNotFound
                       :> (ZLocalUser
                           :> (ZConn
                               :> ("conversations"
                                   :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                       :> ("code"
                                           :> MultiVerb
                                                'DELETE
                                                '[JSON]
                                                '[Respond 200 "Conversation code deleted." Event]
                                                Event))))))))
            :<|> (Named
                    "get-code"
                    (Summary "Get existing conversation code"
                     :> (CanThrow 'CodeNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'GuestLinksDisabled
                                     :> (ZHostOpt
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[Respond
                                                                  200
                                                                  "Conversation Code"
                                                                  ConversationCodeInfo]
                                                              ConversationCodeInfo))))))))))
                  :<|> (Named
                          "member-typing-unqualified"
                          (Summary "Sending typing notifications"
                           :> (Until 'V3
                               :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                   :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                       :> (CanThrow 'ConvNotFound
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("typing"
                                                               :> (ReqBody '[JSON] TypingStatus
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            200 "Notification sent"]
                                                                        ())))))))))))
                        :<|> (Named
                                "member-typing-qualified"
                                (Summary "Sending typing notifications"
                                 :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                     :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                         :> (CanThrow 'ConvNotFound
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("typing"
                                                                 :> (ReqBody '[JSON] TypingStatus
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          '[RespondEmpty
                                                                              200
                                                                              "Notification sent"]
                                                                          ()))))))))))
                              :<|> (Named
                                      "remove-member-unqualified"
                                      (Summary "Remove a member from a conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "leave-conversation"
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (Until 'V2
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Target User ID"]
                                                                                                 "usr"
                                                                                                 UserId
                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                    :<|> (Named
                                            "remove-member"
                                            (Summary "Remove a member from a conversation"
                                             :> (MakesFederatedCall 'Galley "leave-conversation"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'RemoveConversationMember)
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("members"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Target User ID"]
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                          :<|> (Named
                                                  "update-other-member-unqualified"
                                                  (Summary
                                                     "Update membership of the specified user (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'ConvMemberNotFound
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyOtherConversationMember)
                                                                                           :> (CanThrow
                                                                                                 'InvalidTarget
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("members"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Target User ID"]
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         OtherMemberUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                200
                                                                                                                                "Membership updated"]
                                                                                                                            ()))))))))))))))))))
                                                :<|> (Named
                                                        "update-other-member"
                                                        (Summary
                                                           "Update membership of the specified user"
                                                         :> (Description
                                                               "**Note**: at least one field has to be provided."
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvMemberNotFound
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyOtherConversationMember)
                                                                                             :> (CanThrow
                                                                                                   'InvalidTarget
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("members"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Target User ID"]
                                                                                                                       "usr"
                                                                                                                       UserId
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           OtherMemberUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Membership updated"]
                                                                                                                              ())))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name-deprecated"
                                                              (Summary
                                                                 "Update conversation name (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationName)
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationRename
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Name unchanged"
                                                                                                                           "Name updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event)))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name-unqualified"
                                                                    (Summary
                                                                       "Update conversation name (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationName)
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("name"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               ConversationRename
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Name unchanged"
                                                                                                                                     "Name updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name"
                                                                          (Summary
                                                                             "Update conversation name"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationName)
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("name"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             ConversationRename
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                (UpdateResponses
                                                                                                                                   "Name updated"
                                                                                                                                   "Name unchanged"
                                                                                                                                   Event)
                                                                                                                                (UpdateResult
                                                                                                                                   Event))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-message-timer-unqualified"
                                                                                (Summary
                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("message-timer"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  (UpdateResponses
                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                     "Message timer updated"
                                                                                                                                                     Event)
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-message-timer"
                                                                                      (Summary
                                                                                         "Update the message timer for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("message-timer"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                   "Message timer updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                            (Summary
                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "update-conversation"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-receipt-mode"
                                                                                                  (Summary
                                                                                                     "Update receipt mode for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "update-conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access-unqualified"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (Description
                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("access"
                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                               'V2
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access@v2"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("access"
                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                 'V2
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (From
                                                                                                                                       'V3
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("access"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("self"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Maybe
                                                                                                                                                       Member)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("self"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       MemberUpdate
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "Update successful"]
                                                                                                                                                                          ()))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-self"
                                                                                                                                      (Summary
                                                                                                                                         "Update self membership properties"
                                                                                                                                       :> (Description
                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("self"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         MemberUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                200
                                                                                                                                                                                "Update successful"]
                                                                                                                                                                            ())))))))))
                                                                                                                                    :<|> Named
                                                                                                                                           "update-conversation-protocol"
                                                                                                                                           (Summary
                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                            :> (From
                                                                                                                                                  'V5
                                                                                                                                                :> (Description
                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'ConvNotFound
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "create-conversation-code-unqualified"
        (Summary "Create or recreate a conversation code"
         :> (From 'V4
             :> (DescriptionOAuthScope 'WriteConversationsCode
                 :> (CanThrow 'ConvAccessDenied
                     :> (CanThrow 'ConvNotFound
                         :> (CanThrow 'GuestLinksDisabled
                             :> (CanThrow 'CreateConversationCodeConflict
                                 :> (ZUser
                                     :> (ZHostOpt
                                         :> (ZOptConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> (ReqBody
                                                               '[JSON] CreateConversationCodeRequest
                                                             :> CreateConversationCodeVerb))))))))))))))
      :<|> (Named
              "get-conversation-guest-links-status"
              (Summary
                 "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
               :> (CanThrow 'ConvAccessDenied
                   :> (CanThrow 'ConvNotFound
                       :> (ZUser
                           :> ("conversations"
                               :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                   :> ("features"
                                       :> ("conversationGuestLinks"
                                           :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))
            :<|> (Named
                    "remove-code-unqualified"
                    (Summary "Delete conversation code"
                     :> (CanThrow 'ConvAccessDenied
                         :> (CanThrow 'ConvNotFound
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> ("conversations"
                                         :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                             :> ("code"
                                                 :> MultiVerb
                                                      'DELETE
                                                      '[JSON]
                                                      '[Respond
                                                          200 "Conversation code deleted." Event]
                                                      Event))))))))
                  :<|> (Named
                          "get-code"
                          (Summary "Get existing conversation code"
                           :> (CanThrow 'CodeNotFound
                               :> (CanThrow 'ConvAccessDenied
                                   :> (CanThrow 'ConvNotFound
                                       :> (CanThrow 'GuestLinksDisabled
                                           :> (ZHostOpt
                                               :> (ZLocalUser
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("code"
                                                               :> MultiVerb
                                                                    'GET
                                                                    '[JSON]
                                                                    '[Respond
                                                                        200
                                                                        "Conversation Code"
                                                                        ConversationCodeInfo]
                                                                    ConversationCodeInfo))))))))))
                        :<|> (Named
                                "member-typing-unqualified"
                                (Summary "Sending typing notifications"
                                 :> (Until 'V3
                                     :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                         :> (MakesFederatedCall
                                               'Galley "on-typing-indicator-updated"
                                             :> (CanThrow 'ConvNotFound
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("typing"
                                                                     :> (ReqBody
                                                                           '[JSON] TypingStatus
                                                                         :> MultiVerb
                                                                              'POST
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200
                                                                                  "Notification sent"]
                                                                              ())))))))))))
                              :<|> (Named
                                      "member-typing-qualified"
                                      (Summary "Sending typing notifications"
                                       :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                           :> (MakesFederatedCall
                                                 'Galley "on-typing-indicator-updated"
                                               :> (CanThrow 'ConvNotFound
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("typing"
                                                                       :> (ReqBody
                                                                             '[JSON] TypingStatus
                                                                           :> MultiVerb
                                                                                'POST
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "Notification sent"]
                                                                                ()))))))))))
                                    :<|> (Named
                                            "remove-member-unqualified"
                                            (Summary
                                               "Remove a member from a conversation (deprecated)"
                                             :> (MakesFederatedCall 'Galley "leave-conversation"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (Until 'V2
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("members"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Target User ID"]
                                                                                                       "usr"
                                                                                                       UserId
                                                                                                     :> RemoveFromConversationVerb)))))))))))))))
                                          :<|> (Named
                                                  "remove-member"
                                                  (Summary "Remove a member from a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "leave-conversation"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'RemoveConversationMember)
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("members"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Target User ID"]
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> RemoveFromConversationVerb))))))))))))))
                                                :<|> (Named
                                                        "update-other-member-unqualified"
                                                        (Summary
                                                           "Update membership of the specified user (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'ConvMemberNotFound
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyOtherConversationMember)
                                                                                                 :> (CanThrow
                                                                                                       'InvalidTarget
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("members"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Target User ID"]
                                                                                                                           "usr"
                                                                                                                           UserId
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               OtherMemberUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  '[RespondEmpty
                                                                                                                                      200
                                                                                                                                      "Membership updated"]
                                                                                                                                  ()))))))))))))))))))
                                                      :<|> (Named
                                                              "update-other-member"
                                                              (Summary
                                                                 "Update membership of the specified user"
                                                               :> (Description
                                                                     "**Note**: at least one field has to be provided."
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-conversation-updated"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-mls-message-sent"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'ConvMemberNotFound
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyOtherConversationMember)
                                                                                                   :> (CanThrow
                                                                                                         'InvalidTarget
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("members"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Target User ID"]
                                                                                                                             "usr"
                                                                                                                             UserId
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 OtherMemberUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    '[RespondEmpty
                                                                                                                                        200
                                                                                                                                        "Membership updated"]
                                                                                                                                    ())))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name-deprecated"
                                                                    (Summary
                                                                       "Update conversation name (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationName)
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationRename
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Name unchanged"
                                                                                                                                 "Name updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event)))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name-unqualified"
                                                                          (Summary
                                                                             "Update conversation name (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/name` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationName)
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("name"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationRename
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Name unchanged"
                                                                                                                                           "Name updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-name"
                                                                                (Summary
                                                                                   "Update conversation name"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationName)
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (QualifiedCapture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("name"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   ConversationRename
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      (UpdateResponses
                                                                                                                                         "Name updated"
                                                                                                                                         "Name unchanged"
                                                                                                                                         Event)
                                                                                                                                      (UpdateResult
                                                                                                                                         Event))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-message-timer-unqualified"
                                                                                      (Summary
                                                                                         "Update the message timer for a conversation (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Brig
                                                                                                             "get-users-by-ids"
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'ModifyConversationMessageTimer)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("message-timer"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        (UpdateResponses
                                                                                                                                                           "Message timer unchanged"
                                                                                                                                                           "Message timer updated"
                                                                                                                                                           Event)
                                                                                                                                                        (UpdateResult
                                                                                                                                                           Event)))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-message-timer"
                                                                                            (Summary
                                                                                               "Update the message timer for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationMessageTimer)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("message-timer"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Message timer unchanged"
                                                                                                                                                         "Message timer updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-receipt-mode-unqualified"
                                                                                                  (Summary
                                                                                                     "Update receipt mode for a conversation (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "on-conversation-updated"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-mls-message-sent"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "update-conversation"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'ModifyConversationReceiptMode)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (Capture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("receipt-mode"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                                                           "Receipt mode updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-receipt-mode"
                                                                                                        (Summary
                                                                                                           "Update receipt mode for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Galley
                                                                                                                       "update-conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Brig
                                                                                                                           "get-users-by-ids"
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvAccessDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidOperation
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("receipt-mode"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation (deprecated)"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (Description
                                                                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'ModifyConversationAccess)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     ('ActionDenied
                                                                                                                                                        'RemoveConversationMember)
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvAccessDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'ConvNotFound
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidOperation
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                                   :> ("conversations"
                                                                                                                                                                       :> (Capture'
                                                                                                                                                                             '[Description
                                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                                             "cnv"
                                                                                                                                                                             ConvId
                                                                                                                                                                           :> ("access"
                                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                                     'V2
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                                        'PUT
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                                           "Access updated"
                                                                                                                                                                                           Event)
                                                                                                                                                                                        (UpdateResult
                                                                                                                                                                                           Event)))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access@v2"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (Until
                                                                                                                                       'V3
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("access"
                                                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                                                       'V2
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-access"
                                                                                                                          (Summary
                                                                                                                             "Update access modes for a conversation"
                                                                                                                           :> (MakesFederatedCall
                                                                                                                                 'Galley
                                                                                                                                 "on-conversation-updated"
                                                                                                                               :> (MakesFederatedCall
                                                                                                                                     'Galley
                                                                                                                                     "on-mls-message-sent"
                                                                                                                                   :> (MakesFederatedCall
                                                                                                                                         'Brig
                                                                                                                                         "get-users-by-ids"
                                                                                                                                       :> (From
                                                                                                                                             'V3
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> (ZConn
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         ('ActionDenied
                                                                                                                                                            'ModifyConversationAccess)
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             ('ActionDenied
                                                                                                                                                                'RemoveConversationMember)
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'ConvAccessDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'ConvNotFound
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'InvalidOperation
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'InvalidTargetAccess
                                                                                                                                                                           :> ("conversations"
                                                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                                                     '[Description
                                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                                     "cnv"
                                                                                                                                                                                     ConvId
                                                                                                                                                                                   :> ("access"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             ConversationAccessData
                                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                                'PUT
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (UpdateResponses
                                                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                                                   "Access updated"
                                                                                                                                                                                                   Event)
                                                                                                                                                                                                (UpdateResult
                                                                                                                                                                                                   Event))))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-conversation-self-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Get self membership properties (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (Maybe
                                                                                                                                                             Member)))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-self-unqualified"
                                                                                                                                      (Summary
                                                                                                                                         "Update self membership properties (deprecated)"
                                                                                                                                       :> (Deprecated
                                                                                                                                           :> (Description
                                                                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvNotFound
                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                       :> (ZConn
                                                                                                                                                           :> ("conversations"
                                                                                                                                                               :> (Capture'
                                                                                                                                                                     '[Description
                                                                                                                                                                         "Conversation ID"]
                                                                                                                                                                     "cnv"
                                                                                                                                                                     ConvId
                                                                                                                                                                   :> ("self"
                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             MemberUpdate
                                                                                                                                                                           :> MultiVerb
                                                                                                                                                                                'PUT
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                                    200
                                                                                                                                                                                    "Update successful"]
                                                                                                                                                                                ()))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "update-conversation-self"
                                                                                                                                            (Summary
                                                                                                                                               "Update self membership properties"
                                                                                                                                             :> (Description
                                                                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (ZLocalUser
                                                                                                                                                         :> (ZConn
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("self"
                                                                                                                                                                         :> (ReqBody
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               MemberUpdate
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  '[RespondEmpty
                                                                                                                                                                                      200
                                                                                                                                                                                      "Update successful"]
                                                                                                                                                                                  ())))))))))
                                                                                                                                          :<|> Named
                                                                                                                                                 "update-conversation-protocol"
                                                                                                                                                 (Summary
                                                                                                                                                    "Update the protocol of the conversation"
                                                                                                                                                  :> (From
                                                                                                                                                        'V5
                                                                                                                                                      :> (Description
                                                                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'ConvNotFound
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        ('ActionDenied
                                                                                                                                                                           'LeaveConversation)
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'InvalidOperation
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                          :> (ZLocalUser
                                                                                                                                                                                              :> (ZConn
                                                                                                                                                                                                  :> ("conversations"
                                                                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                                                                            '[Description
                                                                                                                                                                                                                "Conversation ID"]
                                                                                                                                                                                                            "cnv"
                                                                                                                                                                                                            ConvId
                                                                                                                                                                                                          :> ("protocol"
                                                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                                                                       'PUT
                                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                                                                       (UpdateResult
                                                                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation-guest-links-status" ServerT
  (Summary
     "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
   :> (CanThrow 'ConvAccessDenied
       :> (CanThrow 'ConvNotFound
           :> (ZUser
               :> ("conversations"
                   :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                       :> ("features"
                           :> ("conversationGuestLinks"
                               :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
            :> (CanThrow 'ConvAccessDenied
                :> (CanThrow 'ConvNotFound
                    :> (ZUser
                        :> ("conversations"
                            :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                :> ("features"
                                    :> ("conversationGuestLinks"
                                        :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
UserId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature GuestLinksConfig)
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Input Opts) r, Member TeamFeatureStore r) =>
UserId -> ConvId -> Sem r (LockableFeature GuestLinksConfig)
getConversationGuestLinksStatus
    API
  (Named
     "get-conversation-guest-links-status"
     (Summary
        "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
      :> (CanThrow 'ConvAccessDenied
          :> (CanThrow 'ConvNotFound
              :> (ZUser
                  :> ("conversations"
                      :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                          :> ("features"
                              :> ("conversationGuestLinks"
                                  :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "remove-code-unqualified"
        (Summary "Delete conversation code"
         :> (CanThrow 'ConvAccessDenied
             :> (CanThrow 'ConvNotFound
                 :> (ZLocalUser
                     :> (ZConn
                         :> ("conversations"
                             :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                 :> ("code"
                                     :> MultiVerb
                                          'DELETE
                                          '[JSON]
                                          '[Respond 200 "Conversation code deleted." Event]
                                          Event))))))))
      :<|> (Named
              "get-code"
              (Summary "Get existing conversation code"
               :> (CanThrow 'CodeNotFound
                   :> (CanThrow 'ConvAccessDenied
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'GuestLinksDisabled
                               :> (ZHostOpt
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("code"
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[Respond
                                                            200
                                                            "Conversation Code"
                                                            ConversationCodeInfo]
                                                        ConversationCodeInfo))))))))))
            :<|> (Named
                    "member-typing-unqualified"
                    (Summary "Sending typing notifications"
                     :> (Until 'V3
                         :> (MakesFederatedCall 'Galley "update-typing-indicator"
                             :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                 :> (CanThrow 'ConvNotFound
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("typing"
                                                         :> (ReqBody '[JSON] TypingStatus
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "Notification sent"]
                                                                  ())))))))))))
                  :<|> (Named
                          "member-typing-qualified"
                          (Summary "Sending typing notifications"
                           :> (MakesFederatedCall 'Galley "update-typing-indicator"
                               :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                   :> (CanThrow 'ConvNotFound
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (QualifiedCapture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("typing"
                                                           :> (ReqBody '[JSON] TypingStatus
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    '[RespondEmpty
                                                                        200 "Notification sent"]
                                                                    ()))))))))))
                        :<|> (Named
                                "remove-member-unqualified"
                                (Summary "Remove a member from a conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "leave-conversation"
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (Until 'V2
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("members"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Target User ID"]
                                                                                           "usr"
                                                                                           UserId
                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                              :<|> (Named
                                      "remove-member"
                                      (Summary "Remove a member from a conversation"
                                       :> (MakesFederatedCall 'Galley "leave-conversation"
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'RemoveConversationMember)
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("members"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Target User ID"]
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                    :<|> (Named
                                            "update-other-member-unqualified"
                                            (Summary
                                               "Update membership of the specified user (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'ConvMemberNotFound
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyOtherConversationMember)
                                                                                     :> (CanThrow
                                                                                           'InvalidTarget
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("members"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Target User ID"]
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   OtherMemberUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "Membership updated"]
                                                                                                                      ()))))))))))))))))))
                                          :<|> (Named
                                                  "update-other-member"
                                                  (Summary "Update membership of the specified user"
                                                   :> (Description
                                                         "**Note**: at least one field has to be provided."
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'ConvMemberNotFound
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyOtherConversationMember)
                                                                                       :> (CanThrow
                                                                                             'InvalidTarget
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("members"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Target User ID"]
                                                                                                                 "usr"
                                                                                                                 UserId
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     OtherMemberUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Membership updated"]
                                                                                                                        ())))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name-deprecated"
                                                        (Summary
                                                           "Update conversation name (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationName)
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationRename
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Name unchanged"
                                                                                                                     "Name updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event)))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name-unqualified"
                                                              (Summary
                                                                 "Update conversation name (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationName)
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("name"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         ConversationRename
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Name unchanged"
                                                                                                                               "Name updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name"
                                                                    (Summary
                                                                       "Update conversation name"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationName)
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("name"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       ConversationRename
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          (UpdateResponses
                                                                                                                             "Name updated"
                                                                                                                             "Name unchanged"
                                                                                                                             Event)
                                                                                                                          (UpdateResult
                                                                                                                             Event))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-message-timer-unqualified"
                                                                          (Summary
                                                                             "Update the message timer for a conversation (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'ModifyConversationMessageTimer)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("message-timer"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            (UpdateResponses
                                                                                                                                               "Message timer unchanged"
                                                                                                                                               "Message timer updated"
                                                                                                                                               Event)
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-message-timer"
                                                                                (Summary
                                                                                   "Update the message timer for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationMessageTimer)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("message-timer"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Message timer unchanged"
                                                                                                                                             "Message timer updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event)))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                      (Summary
                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "update-conversation"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-receipt-mode"
                                                                                            (Summary
                                                                                               "Update receipt mode for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "update-conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access-unqualified"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (Description
                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'RemoveConversationMember)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("access"
                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                         'V2
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                               "Access updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access@v2"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("access"
                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                           'V2
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (From
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("access"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("self"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (Maybe
                                                                                                                                                 Member)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("self"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 MemberUpdate
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "Update successful"]
                                                                                                                                                                    ()))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-self"
                                                                                                                                (Summary
                                                                                                                                   "Update self membership properties"
                                                                                                                                 :> (Description
                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("self"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   MemberUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                          200
                                                                                                                                                                          "Update successful"]
                                                                                                                                                                      ())))))))))
                                                                                                                              :<|> Named
                                                                                                                                     "update-conversation-protocol"
                                                                                                                                     (Summary
                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                      :> (From
                                                                                                                                            'V5
                                                                                                                                          :> (Description
                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'ConvNotFound
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            ('ActionDenied
                                                                                                                                                               'LeaveConversation)
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'InvalidOperation
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            OperationDenied
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                '[Description
                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                ConvId
                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation-guest-links-status"
        (Summary
           "Get the status of the guest links feature for a conversation that potentially has been created by someone from another team."
         :> (CanThrow 'ConvAccessDenied
             :> (CanThrow 'ConvNotFound
                 :> (ZUser
                     :> ("conversations"
                         :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                             :> ("features"
                                 :> ("conversationGuestLinks"
                                     :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))
      :<|> (Named
              "remove-code-unqualified"
              (Summary "Delete conversation code"
               :> (CanThrow 'ConvAccessDenied
                   :> (CanThrow 'ConvNotFound
                       :> (ZLocalUser
                           :> (ZConn
                               :> ("conversations"
                                   :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                       :> ("code"
                                           :> MultiVerb
                                                'DELETE
                                                '[JSON]
                                                '[Respond 200 "Conversation code deleted." Event]
                                                Event))))))))
            :<|> (Named
                    "get-code"
                    (Summary "Get existing conversation code"
                     :> (CanThrow 'CodeNotFound
                         :> (CanThrow 'ConvAccessDenied
                             :> (CanThrow 'ConvNotFound
                                 :> (CanThrow 'GuestLinksDisabled
                                     :> (ZHostOpt
                                         :> (ZLocalUser
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("code"
                                                         :> MultiVerb
                                                              'GET
                                                              '[JSON]
                                                              '[Respond
                                                                  200
                                                                  "Conversation Code"
                                                                  ConversationCodeInfo]
                                                              ConversationCodeInfo))))))))))
                  :<|> (Named
                          "member-typing-unqualified"
                          (Summary "Sending typing notifications"
                           :> (Until 'V3
                               :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                   :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                       :> (CanThrow 'ConvNotFound
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> ("conversations"
                                                       :> (Capture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("typing"
                                                               :> (ReqBody '[JSON] TypingStatus
                                                                   :> MultiVerb
                                                                        'POST
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            200 "Notification sent"]
                                                                        ())))))))))))
                        :<|> (Named
                                "member-typing-qualified"
                                (Summary "Sending typing notifications"
                                 :> (MakesFederatedCall 'Galley "update-typing-indicator"
                                     :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                         :> (CanThrow 'ConvNotFound
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("typing"
                                                                 :> (ReqBody '[JSON] TypingStatus
                                                                     :> MultiVerb
                                                                          'POST
                                                                          '[JSON]
                                                                          '[RespondEmpty
                                                                              200
                                                                              "Notification sent"]
                                                                          ()))))))))))
                              :<|> (Named
                                      "remove-member-unqualified"
                                      (Summary "Remove a member from a conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "leave-conversation"
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (Until 'V2
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("members"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Target User ID"]
                                                                                                 "usr"
                                                                                                 UserId
                                                                                               :> RemoveFromConversationVerb)))))))))))))))
                                    :<|> (Named
                                            "remove-member"
                                            (Summary "Remove a member from a conversation"
                                             :> (MakesFederatedCall 'Galley "leave-conversation"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'RemoveConversationMember)
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("members"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Target User ID"]
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> RemoveFromConversationVerb))))))))))))))
                                          :<|> (Named
                                                  "update-other-member-unqualified"
                                                  (Summary
                                                     "Update membership of the specified user (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'ConvMemberNotFound
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyOtherConversationMember)
                                                                                           :> (CanThrow
                                                                                                 'InvalidTarget
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("members"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Target User ID"]
                                                                                                                     "usr"
                                                                                                                     UserId
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         OtherMemberUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                200
                                                                                                                                "Membership updated"]
                                                                                                                            ()))))))))))))))))))
                                                :<|> (Named
                                                        "update-other-member"
                                                        (Summary
                                                           "Update membership of the specified user"
                                                         :> (Description
                                                               "**Note**: at least one field has to be provided."
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-conversation-updated"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "on-mls-message-sent"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'ConvMemberNotFound
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyOtherConversationMember)
                                                                                             :> (CanThrow
                                                                                                   'InvalidTarget
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("members"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Target User ID"]
                                                                                                                       "usr"
                                                                                                                       UserId
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           OtherMemberUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              '[RespondEmpty
                                                                                                                                  200
                                                                                                                                  "Membership updated"]
                                                                                                                              ())))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name-deprecated"
                                                              (Summary
                                                                 "Update conversation name (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationName)
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationRename
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Name unchanged"
                                                                                                                           "Name updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event)))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name-unqualified"
                                                                    (Summary
                                                                       "Update conversation name (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/name` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationName)
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("name"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               ConversationRename
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Name unchanged"
                                                                                                                                     "Name updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-name"
                                                                          (Summary
                                                                             "Update conversation name"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationName)
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (QualifiedCapture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("name"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             ConversationRename
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                (UpdateResponses
                                                                                                                                   "Name updated"
                                                                                                                                   "Name unchanged"
                                                                                                                                   Event)
                                                                                                                                (UpdateResult
                                                                                                                                   Event))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-message-timer-unqualified"
                                                                                (Summary
                                                                                   "Update the message timer for a conversation (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Brig
                                                                                                       "get-users-by-ids"
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'ModifyConversationMessageTimer)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("message-timer"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               ConversationMessageTimerUpdate
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  (UpdateResponses
                                                                                                                                                     "Message timer unchanged"
                                                                                                                                                     "Message timer updated"
                                                                                                                                                     Event)
                                                                                                                                                  (UpdateResult
                                                                                                                                                     Event)))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-message-timer"
                                                                                      (Summary
                                                                                         "Update the message timer for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationMessageTimer)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("message-timer"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Message timer unchanged"
                                                                                                                                                   "Message timer updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event)))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-receipt-mode-unqualified"
                                                                                            (Summary
                                                                                               "Update receipt mode for a conversation (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "on-conversation-updated"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-mls-message-sent"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "update-conversation"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'ModifyConversationReceiptMode)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (Capture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("receipt-mode"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                                                     "Receipt mode updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-receipt-mode"
                                                                                                  (Summary
                                                                                                     "Update receipt mode for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Galley
                                                                                                                 "update-conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Brig
                                                                                                                     "get-users-by-ids"
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvAccessDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidOperation
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("receipt-mode"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access-unqualified"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation (deprecated)"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (Description
                                                                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'ModifyConversationAccess)
                                                                                                                                         :> (CanThrow
                                                                                                                                               ('ActionDenied
                                                                                                                                                  'RemoveConversationMember)
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvAccessDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'ConvNotFound
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidOperation
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'InvalidTargetAccess
                                                                                                                                                             :> ("conversations"
                                                                                                                                                                 :> (Capture'
                                                                                                                                                                       '[Description
                                                                                                                                                                           "Conversation ID"]
                                                                                                                                                                       "cnv"
                                                                                                                                                                       ConvId
                                                                                                                                                                     :> ("access"
                                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                                               'V2
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               ConversationAccessData
                                                                                                                                                                             :> MultiVerb
                                                                                                                                                                                  'PUT
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                                     "Access updated"
                                                                                                                                                                                     Event)
                                                                                                                                                                                  (UpdateResult
                                                                                                                                                                                     Event)))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access@v2"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (Until
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("access"
                                                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                                                 'V2
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-access"
                                                                                                                    (Summary
                                                                                                                       "Update access modes for a conversation"
                                                                                                                     :> (MakesFederatedCall
                                                                                                                           'Galley
                                                                                                                           "on-conversation-updated"
                                                                                                                         :> (MakesFederatedCall
                                                                                                                               'Galley
                                                                                                                               "on-mls-message-sent"
                                                                                                                             :> (MakesFederatedCall
                                                                                                                                   'Brig
                                                                                                                                   "get-users-by-ids"
                                                                                                                                 :> (From
                                                                                                                                       'V3
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> (ZConn
                                                                                                                                             :> (CanThrow
                                                                                                                                                   ('ActionDenied
                                                                                                                                                      'ModifyConversationAccess)
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       ('ActionDenied
                                                                                                                                                          'RemoveConversationMember)
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'ConvAccessDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'ConvNotFound
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'InvalidOperation
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'InvalidTargetAccess
                                                                                                                                                                     :> ("conversations"
                                                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                                                               '[Description
                                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                                               "cnv"
                                                                                                                                                                               ConvId
                                                                                                                                                                             :> ("access"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       ConversationAccessData
                                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                                          'PUT
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (UpdateResponses
                                                                                                                                                                                             "Access unchanged"
                                                                                                                                                                                             "Access updated"
                                                                                                                                                                                             Event)
                                                                                                                                                                                          (UpdateResult
                                                                                                                                                                                             Event))))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-conversation-self-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Get self membership properties (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("self"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (Maybe
                                                                                                                                                       Member)))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-self-unqualified"
                                                                                                                                (Summary
                                                                                                                                   "Update self membership properties (deprecated)"
                                                                                                                                 :> (Deprecated
                                                                                                                                     :> (Description
                                                                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvNotFound
                                                                                                                                             :> (ZLocalUser
                                                                                                                                                 :> (ZConn
                                                                                                                                                     :> ("conversations"
                                                                                                                                                         :> (Capture'
                                                                                                                                                               '[Description
                                                                                                                                                                   "Conversation ID"]
                                                                                                                                                               "cnv"
                                                                                                                                                               ConvId
                                                                                                                                                             :> ("self"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       MemberUpdate
                                                                                                                                                                     :> MultiVerb
                                                                                                                                                                          'PUT
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          '[RespondEmpty
                                                                                                                                                                              200
                                                                                                                                                                              "Update successful"]
                                                                                                                                                                          ()))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "update-conversation-self"
                                                                                                                                      (Summary
                                                                                                                                         "Update self membership properties"
                                                                                                                                       :> (Description
                                                                                                                                             "**Note**: at least one field has to be provided."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (ZLocalUser
                                                                                                                                                   :> (ZConn
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("self"
                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         MemberUpdate
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            '[RespondEmpty
                                                                                                                                                                                200
                                                                                                                                                                                "Update successful"]
                                                                                                                                                                            ())))))))))
                                                                                                                                    :<|> Named
                                                                                                                                           "update-conversation-protocol"
                                                                                                                                           (Summary
                                                                                                                                              "Update the protocol of the conversation"
                                                                                                                                            :> (From
                                                                                                                                                  'V5
                                                                                                                                                :> (Description
                                                                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'ConvNotFound
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'ConvInvalidProtocolTransition
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  ('ActionDenied
                                                                                                                                                                     'LeaveConversation)
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'InvalidOperation
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                    :> (ZLocalUser
                                                                                                                                                                                        :> (ZConn
                                                                                                                                                                                            :> ("conversations"
                                                                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                                                                      '[Description
                                                                                                                                                                                                          "Conversation ID"]
                                                                                                                                                                                                      "cnv"
                                                                                                                                                                                                      ConvId
                                                                                                                                                                                                    :> ("protocol"
                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                              ProtocolUpdate
                                                                                                                                                                                                            :> MultiVerb
                                                                                                                                                                                                                 'PUT
                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                                                                 (UpdateResult
                                                                                                                                                                                                                    Event))))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"remove-code-unqualified" ServerT
  (Summary "Delete conversation code"
   :> (CanThrow 'ConvAccessDenied
       :> (CanThrow 'ConvNotFound
           :> (ZLocalUser
               :> (ZConn
                   :> ("conversations"
                       :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                           :> ("code"
                               :> MultiVerb
                                    'DELETE
                                    '[JSON]
                                    '[Respond 200 "Conversation code deleted." Event]
                                    Event))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Delete conversation code"
            :> (CanThrow 'ConvAccessDenied
                :> (CanThrow 'ConvNotFound
                    :> (ZLocalUser
                        :> (ZConn
                            :> ("conversations"
                                :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                    :> ("code"
                                        :> MultiVerb
                                             'DELETE
                                             '[JSON]
                                             '[Respond 200 "Conversation code deleted." Event]
                                             Event)))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> Sem
     '[Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     Event
forall (r :: EffectRow).
(Member CodeStore r, Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input (Local ())) r, Member (Input UTCTime) r) =>
QualifiedWithTag 'QLocal UserId -> ConnId -> ConvId -> Sem r Event
rmCodeUnqualified
    API
  (Named
     "remove-code-unqualified"
     (Summary "Delete conversation code"
      :> (CanThrow 'ConvAccessDenied
          :> (CanThrow 'ConvNotFound
              :> (ZLocalUser
                  :> (ZConn
                      :> ("conversations"
                          :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                              :> ("code"
                                  :> MultiVerb
                                       'DELETE
                                       '[JSON]
                                       '[Respond 200 "Conversation code deleted." Event]
                                       Event)))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-code"
        (Summary "Get existing conversation code"
         :> (CanThrow 'CodeNotFound
             :> (CanThrow 'ConvAccessDenied
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'GuestLinksDisabled
                         :> (ZHostOpt
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("code"
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[Respond
                                                      200 "Conversation Code" ConversationCodeInfo]
                                                  ConversationCodeInfo))))))))))
      :<|> (Named
              "member-typing-unqualified"
              (Summary "Sending typing notifications"
               :> (Until 'V3
                   :> (MakesFederatedCall 'Galley "update-typing-indicator"
                       :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("typing"
                                                   :> (ReqBody '[JSON] TypingStatus
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty 200 "Notification sent"]
                                                            ())))))))))))
            :<|> (Named
                    "member-typing-qualified"
                    (Summary "Sending typing notifications"
                     :> (MakesFederatedCall 'Galley "update-typing-indicator"
                         :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                             :> (CanThrow 'ConvNotFound
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (QualifiedCapture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("typing"
                                                     :> (ReqBody '[JSON] TypingStatus
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[RespondEmpty
                                                                  200 "Notification sent"]
                                                              ()))))))))))
                  :<|> (Named
                          "remove-member-unqualified"
                          (Summary "Remove a member from a conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "leave-conversation"
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (Until 'V2
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("members"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Target User ID"]
                                                                                     "usr"
                                                                                     UserId
                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                        :<|> (Named
                                "remove-member"
                                (Summary "Remove a member from a conversation"
                                 :> (MakesFederatedCall 'Galley "leave-conversation"
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'RemoveConversationMember)
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("members"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Target User ID"]
                                                                                       "usr"
                                                                                       UserId
                                                                                     :> RemoveFromConversationVerb))))))))))))))
                              :<|> (Named
                                      "update-other-member-unqualified"
                                      (Summary
                                         "Update membership of the specified user (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'ConvMemberNotFound
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyOtherConversationMember)
                                                                               :> (CanThrow
                                                                                     'InvalidTarget
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("members"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Target User ID"]
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             OtherMemberUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "Membership updated"]
                                                                                                                ()))))))))))))))))))
                                    :<|> (Named
                                            "update-other-member"
                                            (Summary "Update membership of the specified user"
                                             :> (Description
                                                   "**Note**: at least one field has to be provided."
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'ConvMemberNotFound
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyOtherConversationMember)
                                                                                 :> (CanThrow
                                                                                       'InvalidTarget
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("members"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Target User ID"]
                                                                                                           "usr"
                                                                                                           UserId
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               OtherMemberUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Membership updated"]
                                                                                                                  ())))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name-deprecated"
                                                  (Summary "Update conversation name (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationName)
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationRename
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Name unchanged"
                                                                                                               "Name updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event)))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name-unqualified"
                                                        (Summary
                                                           "Update conversation name (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationName)
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("name"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   ConversationRename
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Name unchanged"
                                                                                                                         "Name updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name"
                                                              (Summary "Update conversation name"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationName)
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("name"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ConversationRename
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    (UpdateResponses
                                                                                                                       "Name updated"
                                                                                                                       "Name unchanged"
                                                                                                                       Event)
                                                                                                                    (UpdateResult
                                                                                                                       Event))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-message-timer-unqualified"
                                                                    (Summary
                                                                       "Update the message timer for a conversation (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'ModifyConversationMessageTimer)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("message-timer"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      (UpdateResponses
                                                                                                                                         "Message timer unchanged"
                                                                                                                                         "Message timer updated"
                                                                                                                                         Event)
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-message-timer"
                                                                          (Summary
                                                                             "Update the message timer for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationMessageTimer)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("message-timer"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Message timer unchanged"
                                                                                                                                       "Message timer updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event)))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                (Summary
                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "update-conversation"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("receipt-mode"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-receipt-mode"
                                                                                      (Summary
                                                                                         "Update receipt mode for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "update-conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("receipt-mode"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access-unqualified"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (Description
                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'ModifyConversationAccess)
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'RemoveConversationMember)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("access"
                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                   'V2
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                         "Access updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event)))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access@v2"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationAccess)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("access"
                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                     'V2
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                           "Access updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (From
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("access"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-conversation-self-unqualified"
                                                                                                              (Summary
                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("self"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (Maybe
                                                                                                                                           Member)))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           MemberUpdate
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "Update successful"]
                                                                                                                                                              ()))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-self"
                                                                                                                          (Summary
                                                                                                                             "Update self membership properties"
                                                                                                                           :> (Description
                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("self"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             MemberUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                    200
                                                                                                                                                                    "Update successful"]
                                                                                                                                                                ())))))))))
                                                                                                                        :<|> Named
                                                                                                                               "update-conversation-protocol"
                                                                                                                               (Summary
                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                :> (From
                                                                                                                                      'V5
                                                                                                                                    :> (Description
                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                        :> (CanThrow
                                                                                                                                              'ConvNotFound
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                :> (CanThrow
                                                                                                                                                      ('ActionDenied
                                                                                                                                                         'LeaveConversation)
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'InvalidOperation
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      OperationDenied
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                          '[Description
                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                          "cnv"
                                                                                                                                                                                          ConvId
                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "remove-code-unqualified"
        (Summary "Delete conversation code"
         :> (CanThrow 'ConvAccessDenied
             :> (CanThrow 'ConvNotFound
                 :> (ZLocalUser
                     :> (ZConn
                         :> ("conversations"
                             :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                 :> ("code"
                                     :> MultiVerb
                                          'DELETE
                                          '[JSON]
                                          '[Respond 200 "Conversation code deleted." Event]
                                          Event))))))))
      :<|> (Named
              "get-code"
              (Summary "Get existing conversation code"
               :> (CanThrow 'CodeNotFound
                   :> (CanThrow 'ConvAccessDenied
                       :> (CanThrow 'ConvNotFound
                           :> (CanThrow 'GuestLinksDisabled
                               :> (ZHostOpt
                                   :> (ZLocalUser
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("code"
                                                   :> MultiVerb
                                                        'GET
                                                        '[JSON]
                                                        '[Respond
                                                            200
                                                            "Conversation Code"
                                                            ConversationCodeInfo]
                                                        ConversationCodeInfo))))))))))
            :<|> (Named
                    "member-typing-unqualified"
                    (Summary "Sending typing notifications"
                     :> (Until 'V3
                         :> (MakesFederatedCall 'Galley "update-typing-indicator"
                             :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                 :> (CanThrow 'ConvNotFound
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> ("conversations"
                                                 :> (Capture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("typing"
                                                         :> (ReqBody '[JSON] TypingStatus
                                                             :> MultiVerb
                                                                  'POST
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      200 "Notification sent"]
                                                                  ())))))))))))
                  :<|> (Named
                          "member-typing-qualified"
                          (Summary "Sending typing notifications"
                           :> (MakesFederatedCall 'Galley "update-typing-indicator"
                               :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                                   :> (CanThrow 'ConvNotFound
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (QualifiedCapture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("typing"
                                                           :> (ReqBody '[JSON] TypingStatus
                                                               :> MultiVerb
                                                                    'POST
                                                                    '[JSON]
                                                                    '[RespondEmpty
                                                                        200 "Notification sent"]
                                                                    ()))))))))))
                        :<|> (Named
                                "remove-member-unqualified"
                                (Summary "Remove a member from a conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "leave-conversation"
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (Until 'V2
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("members"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Target User ID"]
                                                                                           "usr"
                                                                                           UserId
                                                                                         :> RemoveFromConversationVerb)))))))))))))))
                              :<|> (Named
                                      "remove-member"
                                      (Summary "Remove a member from a conversation"
                                       :> (MakesFederatedCall 'Galley "leave-conversation"
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'RemoveConversationMember)
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("members"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Target User ID"]
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> RemoveFromConversationVerb))))))))))))))
                                    :<|> (Named
                                            "update-other-member-unqualified"
                                            (Summary
                                               "Update membership of the specified user (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'ConvMemberNotFound
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyOtherConversationMember)
                                                                                     :> (CanThrow
                                                                                           'InvalidTarget
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("members"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Target User ID"]
                                                                                                               "usr"
                                                                                                               UserId
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   OtherMemberUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "Membership updated"]
                                                                                                                      ()))))))))))))))))))
                                          :<|> (Named
                                                  "update-other-member"
                                                  (Summary "Update membership of the specified user"
                                                   :> (Description
                                                         "**Note**: at least one field has to be provided."
                                                       :> (MakesFederatedCall
                                                             'Galley "on-conversation-updated"
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-mls-message-sent"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'ConvMemberNotFound
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyOtherConversationMember)
                                                                                       :> (CanThrow
                                                                                             'InvalidTarget
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("members"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Target User ID"]
                                                                                                                 "usr"
                                                                                                                 UserId
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     OtherMemberUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        '[RespondEmpty
                                                                                                                            200
                                                                                                                            "Membership updated"]
                                                                                                                        ())))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name-deprecated"
                                                        (Summary
                                                           "Update conversation name (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationName)
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationRename
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Name unchanged"
                                                                                                                     "Name updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event)))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name-unqualified"
                                                              (Summary
                                                                 "Update conversation name (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/name` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationName)
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("name"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         ConversationRename
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Name unchanged"
                                                                                                                               "Name updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-name"
                                                                    (Summary
                                                                       "Update conversation name"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationName)
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (QualifiedCapture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("name"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       ConversationRename
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          (UpdateResponses
                                                                                                                             "Name updated"
                                                                                                                             "Name unchanged"
                                                                                                                             Event)
                                                                                                                          (UpdateResult
                                                                                                                             Event))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-message-timer-unqualified"
                                                                          (Summary
                                                                             "Update the message timer for a conversation (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Brig
                                                                                                 "get-users-by-ids"
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'ModifyConversationMessageTimer)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("message-timer"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         ConversationMessageTimerUpdate
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            (UpdateResponses
                                                                                                                                               "Message timer unchanged"
                                                                                                                                               "Message timer updated"
                                                                                                                                               Event)
                                                                                                                                            (UpdateResult
                                                                                                                                               Event)))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-message-timer"
                                                                                (Summary
                                                                                   "Update the message timer for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationMessageTimer)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("message-timer"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Message timer unchanged"
                                                                                                                                             "Message timer updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event)))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-receipt-mode-unqualified"
                                                                                      (Summary
                                                                                         "Update receipt mode for a conversation (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "on-conversation-updated"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-mls-message-sent"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "update-conversation"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'ModifyConversationReceiptMode)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (Capture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("receipt-mode"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Receipt mode unchanged"
                                                                                                                                                               "Receipt mode updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-receipt-mode"
                                                                                            (Summary
                                                                                               "Update receipt mode for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Galley
                                                                                                           "update-conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Brig
                                                                                                               "get-users-by-ids"
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationReceiptMode)
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvAccessDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidOperation
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("receipt-mode"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                                             "Receipt mode updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access-unqualified"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation (deprecated)"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (Description
                                                                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'ModifyConversationAccess)
                                                                                                                                   :> (CanThrow
                                                                                                                                         ('ActionDenied
                                                                                                                                            'RemoveConversationMember)
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvAccessDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'ConvNotFound
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidOperation
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'InvalidTargetAccess
                                                                                                                                                       :> ("conversations"
                                                                                                                                                           :> (Capture'
                                                                                                                                                                 '[Description
                                                                                                                                                                     "Conversation ID"]
                                                                                                                                                                 "cnv"
                                                                                                                                                                 ConvId
                                                                                                                                                               :> ("access"
                                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                                         'V2
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         ConversationAccessData
                                                                                                                                                                       :> MultiVerb
                                                                                                                                                                            'PUT
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (UpdateResponses
                                                                                                                                                                               "Access unchanged"
                                                                                                                                                                               "Access updated"
                                                                                                                                                                               Event)
                                                                                                                                                                            (UpdateResult
                                                                                                                                                                               Event)))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access@v2"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (Until
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("access"
                                                                                                                                                                     :> (VersionedReqBody
                                                                                                                                                                           'V2
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-access"
                                                                                                              (Summary
                                                                                                                 "Update access modes for a conversation"
                                                                                                               :> (MakesFederatedCall
                                                                                                                     'Galley
                                                                                                                     "on-conversation-updated"
                                                                                                                   :> (MakesFederatedCall
                                                                                                                         'Galley
                                                                                                                         "on-mls-message-sent"
                                                                                                                       :> (MakesFederatedCall
                                                                                                                             'Brig
                                                                                                                             "get-users-by-ids"
                                                                                                                           :> (From
                                                                                                                                 'V3
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> (ZConn
                                                                                                                                       :> (CanThrow
                                                                                                                                             ('ActionDenied
                                                                                                                                                'ModifyConversationAccess)
                                                                                                                                           :> (CanThrow
                                                                                                                                                 ('ActionDenied
                                                                                                                                                    'RemoveConversationMember)
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'ConvAccessDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'ConvNotFound
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'InvalidOperation
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'InvalidTargetAccess
                                                                                                                                                               :> ("conversations"
                                                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                                                         '[Description
                                                                                                                                                                             "Conversation ID"]
                                                                                                                                                                         "cnv"
                                                                                                                                                                         ConvId
                                                                                                                                                                       :> ("access"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 ConversationAccessData
                                                                                                                                                                               :> MultiVerb
                                                                                                                                                                                    'PUT
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (UpdateResponses
                                                                                                                                                                                       "Access unchanged"
                                                                                                                                                                                       "Access updated"
                                                                                                                                                                                       Event)
                                                                                                                                                                                    (UpdateResult
                                                                                                                                                                                       Event))))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-conversation-self-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Get self membership properties (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("self"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (Maybe
                                                                                                                                                 Member)))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-self-unqualified"
                                                                                                                          (Summary
                                                                                                                             "Update self membership properties (deprecated)"
                                                                                                                           :> (Deprecated
                                                                                                                               :> (Description
                                                                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvNotFound
                                                                                                                                       :> (ZLocalUser
                                                                                                                                           :> (ZConn
                                                                                                                                               :> ("conversations"
                                                                                                                                                   :> (Capture'
                                                                                                                                                         '[Description
                                                                                                                                                             "Conversation ID"]
                                                                                                                                                         "cnv"
                                                                                                                                                         ConvId
                                                                                                                                                       :> ("self"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 MemberUpdate
                                                                                                                                                               :> MultiVerb
                                                                                                                                                                    'PUT
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    '[RespondEmpty
                                                                                                                                                                        200
                                                                                                                                                                        "Update successful"]
                                                                                                                                                                    ()))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "update-conversation-self"
                                                                                                                                (Summary
                                                                                                                                   "Update self membership properties"
                                                                                                                                 :> (Description
                                                                                                                                       "**Note**: at least one field has to be provided."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (ZLocalUser
                                                                                                                                             :> (ZConn
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("self"
                                                                                                                                                             :> (ReqBody
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   MemberUpdate
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      '[RespondEmpty
                                                                                                                                                                          200
                                                                                                                                                                          "Update successful"]
                                                                                                                                                                      ())))))))))
                                                                                                                              :<|> Named
                                                                                                                                     "update-conversation-protocol"
                                                                                                                                     (Summary
                                                                                                                                        "Update the protocol of the conversation"
                                                                                                                                      :> (From
                                                                                                                                            'V5
                                                                                                                                          :> (Description
                                                                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'ConvNotFound
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'ConvInvalidProtocolTransition
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            ('ActionDenied
                                                                                                                                                               'LeaveConversation)
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'InvalidOperation
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            OperationDenied
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                              :> (ZLocalUser
                                                                                                                                                                                  :> (ZConn
                                                                                                                                                                                      :> ("conversations"
                                                                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                                                                '[Description
                                                                                                                                                                                                    "Conversation ID"]
                                                                                                                                                                                                "cnv"
                                                                                                                                                                                                ConvId
                                                                                                                                                                                              :> ("protocol"
                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                        ProtocolUpdate
                                                                                                                                                                                                      :> MultiVerb
                                                                                                                                                                                                           'PUT
                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                                                                           (UpdateResult
                                                                                                                                                                                                              Event)))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-code" ServerT
  (Summary "Get existing conversation code"
   :> (CanThrow 'CodeNotFound
       :> (CanThrow 'ConvAccessDenied
           :> (CanThrow 'ConvNotFound
               :> (CanThrow 'GuestLinksDisabled
                   :> (ZHostOpt
                       :> (ZLocalUser
                           :> ("conversations"
                               :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                   :> ("code"
                                       :> MultiVerb
                                            'GET
                                            '[JSON]
                                            '[Respond 200 "Conversation Code" ConversationCodeInfo]
                                            ConversationCodeInfo))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get existing conversation code"
            :> (CanThrow 'CodeNotFound
                :> (CanThrow 'ConvAccessDenied
                    :> (CanThrow 'ConvNotFound
                        :> (CanThrow 'GuestLinksDisabled
                            :> (ZHostOpt
                                :> (ZLocalUser
                                    :> ("conversations"
                                        :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                            :> ("code"
                                                :> MultiVerb
                                                     'GET
                                                     '[JSON]
                                                     '[Respond
                                                         200
                                                         "Conversation Code"
                                                         ConversationCodeInfo]
                                                     ConversationCodeInfo)))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
Maybe Text
-> QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem
     '[Error (Tagged 'CodeNotFound ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'GuestLinksDisabled ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ConversationCodeInfo
forall (r :: EffectRow).
(Member CodeStore r, Member ConversationStore r,
 Member (Error (Tagged 'CodeNotFound ())) r,
 Member (Error (Tagged 'ConvAccessDenied ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'GuestLinksDisabled ())) r,
 Member (Input Opts) r, Member TeamFeatureStore r) =>
Maybe Text
-> QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem r ConversationCodeInfo
getCode
    API
  (Named
     "get-code"
     (Summary "Get existing conversation code"
      :> (CanThrow 'CodeNotFound
          :> (CanThrow 'ConvAccessDenied
              :> (CanThrow 'ConvNotFound
                  :> (CanThrow 'GuestLinksDisabled
                      :> (ZHostOpt
                          :> (ZLocalUser
                              :> ("conversations"
                                  :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                      :> ("code"
                                          :> MultiVerb
                                               'GET
                                               '[JSON]
                                               '[Respond
                                                   200 "Conversation Code" ConversationCodeInfo]
                                               ConversationCodeInfo)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "member-typing-unqualified"
        (Summary "Sending typing notifications"
         :> (Until 'V3
             :> (MakesFederatedCall 'Galley "update-typing-indicator"
                 :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZConn
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("typing"
                                             :> (ReqBody '[JSON] TypingStatus
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Notification sent"]
                                                      ())))))))))))
      :<|> (Named
              "member-typing-qualified"
              (Summary "Sending typing notifications"
               :> (MakesFederatedCall 'Galley "update-typing-indicator"
                   :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                       :> (CanThrow 'ConvNotFound
                           :> (ZLocalUser
                               :> (ZConn
                                   :> ("conversations"
                                       :> (QualifiedCapture'
                                             '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("typing"
                                               :> (ReqBody '[JSON] TypingStatus
                                                   :> MultiVerb
                                                        'POST
                                                        '[JSON]
                                                        '[RespondEmpty 200 "Notification sent"]
                                                        ()))))))))))
            :<|> (Named
                    "remove-member-unqualified"
                    (Summary "Remove a member from a conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "leave-conversation"
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (Until 'V2
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("members"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Target User ID"]
                                                                               "usr"
                                                                               UserId
                                                                             :> RemoveFromConversationVerb)))))))))))))))
                  :<|> (Named
                          "remove-member"
                          (Summary "Remove a member from a conversation"
                           :> (MakesFederatedCall 'Galley "leave-conversation"
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'RemoveConversationMember)
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("members"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Target User ID"]
                                                                                 "usr"
                                                                                 UserId
                                                                               :> RemoveFromConversationVerb))))))))))))))
                        :<|> (Named
                                "update-other-member-unqualified"
                                (Summary "Update membership of the specified user (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'ConvMemberNotFound
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyOtherConversationMember)
                                                                         :> (CanThrow 'InvalidTarget
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("members"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Target User ID"]
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       OtherMemberUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "Membership updated"]
                                                                                                          ()))))))))))))))))))
                              :<|> (Named
                                      "update-other-member"
                                      (Summary "Update membership of the specified user"
                                       :> (Description
                                             "**Note**: at least one field has to be provided."
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'ConvMemberNotFound
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyOtherConversationMember)
                                                                           :> (CanThrow
                                                                                 'InvalidTarget
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("members"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Target User ID"]
                                                                                                     "usr"
                                                                                                     UserId
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         OtherMemberUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Membership updated"]
                                                                                                            ())))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name-deprecated"
                                            (Summary "Update conversation name (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationName)
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationRename
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Name unchanged"
                                                                                                         "Name updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event)))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name-unqualified"
                                                  (Summary "Update conversation name (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationName)
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("name"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             ConversationRename
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Name unchanged"
                                                                                                                   "Name updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name"
                                                        (Summary "Update conversation name"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationName)
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("name"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ConversationRename
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              (UpdateResponses
                                                                                                                 "Name updated"
                                                                                                                 "Name unchanged"
                                                                                                                 Event)
                                                                                                              (UpdateResult
                                                                                                                 Event))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-message-timer-unqualified"
                                                              (Summary
                                                                 "Update the message timer for a conversation (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'ModifyConversationMessageTimer)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("message-timer"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                (UpdateResponses
                                                                                                                                   "Message timer unchanged"
                                                                                                                                   "Message timer updated"
                                                                                                                                   Event)
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-message-timer"
                                                                    (Summary
                                                                       "Update the message timer for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationMessageTimer)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("message-timer"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Message timer unchanged"
                                                                                                                                 "Message timer updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event)))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-receipt-mode-unqualified"
                                                                          (Summary
                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "update-conversation"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("receipt-mode"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-receipt-mode"
                                                                                (Summary
                                                                                   "Update receipt mode for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "update-conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("receipt-mode"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access-unqualified"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (Description
                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'ModifyConversationAccess)
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'RemoveConversationMember)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidTargetAccess
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("access"
                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                             'V2
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationAccessData
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                   "Access updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event)))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access@v2"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationAccess)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidTargetAccess
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("access"
                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                               'V2
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationAccessData
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                     "Access updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (From
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationAccess)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("access"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                           "Access updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-conversation-self-unqualified"
                                                                                                        (Summary
                                                                                                           "Get self membership properties (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("self"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (Maybe
                                                                                                                                     Member)))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-self-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("self"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     MemberUpdate
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "Update successful"]
                                                                                                                                                        ()))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-self"
                                                                                                                    (Summary
                                                                                                                       "Update self membership properties"
                                                                                                                     :> (Description
                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("self"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       MemberUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[RespondEmpty
                                                                                                                                                              200
                                                                                                                                                              "Update successful"]
                                                                                                                                                          ())))))))))
                                                                                                                  :<|> Named
                                                                                                                         "update-conversation-protocol"
                                                                                                                         (Summary
                                                                                                                            "Update the protocol of the conversation"
                                                                                                                          :> (From
                                                                                                                                'V5
                                                                                                                              :> (Description
                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                  :> (CanThrow
                                                                                                                                        'ConvNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                          :> (CanThrow
                                                                                                                                                ('ActionDenied
                                                                                                                                                   'LeaveConversation)
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'InvalidOperation
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'NotATeamMember
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                OperationDenied
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                      :> (ZConn
                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                    '[Description
                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                    "cnv"
                                                                                                                                                                                    ConvId
                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                               'PUT
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-code"
        (Summary "Get existing conversation code"
         :> (CanThrow 'CodeNotFound
             :> (CanThrow 'ConvAccessDenied
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'GuestLinksDisabled
                         :> (ZHostOpt
                             :> (ZLocalUser
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("code"
                                             :> MultiVerb
                                                  'GET
                                                  '[JSON]
                                                  '[Respond
                                                      200 "Conversation Code" ConversationCodeInfo]
                                                  ConversationCodeInfo))))))))))
      :<|> (Named
              "member-typing-unqualified"
              (Summary "Sending typing notifications"
               :> (Until 'V3
                   :> (MakesFederatedCall 'Galley "update-typing-indicator"
                       :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                           :> (CanThrow 'ConvNotFound
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> ("conversations"
                                           :> (Capture'
                                                 '[Description "Conversation ID"] "cnv" ConvId
                                               :> ("typing"
                                                   :> (ReqBody '[JSON] TypingStatus
                                                       :> MultiVerb
                                                            'POST
                                                            '[JSON]
                                                            '[RespondEmpty 200 "Notification sent"]
                                                            ())))))))))))
            :<|> (Named
                    "member-typing-qualified"
                    (Summary "Sending typing notifications"
                     :> (MakesFederatedCall 'Galley "update-typing-indicator"
                         :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                             :> (CanThrow 'ConvNotFound
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (QualifiedCapture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("typing"
                                                     :> (ReqBody '[JSON] TypingStatus
                                                         :> MultiVerb
                                                              'POST
                                                              '[JSON]
                                                              '[RespondEmpty
                                                                  200 "Notification sent"]
                                                              ()))))))))))
                  :<|> (Named
                          "remove-member-unqualified"
                          (Summary "Remove a member from a conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "leave-conversation"
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (Until 'V2
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("members"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Target User ID"]
                                                                                     "usr"
                                                                                     UserId
                                                                                   :> RemoveFromConversationVerb)))))))))))))))
                        :<|> (Named
                                "remove-member"
                                (Summary "Remove a member from a conversation"
                                 :> (MakesFederatedCall 'Galley "leave-conversation"
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'RemoveConversationMember)
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("members"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Target User ID"]
                                                                                       "usr"
                                                                                       UserId
                                                                                     :> RemoveFromConversationVerb))))))))))))))
                              :<|> (Named
                                      "update-other-member-unqualified"
                                      (Summary
                                         "Update membership of the specified user (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'ConvMemberNotFound
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyOtherConversationMember)
                                                                               :> (CanThrow
                                                                                     'InvalidTarget
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("members"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Target User ID"]
                                                                                                         "usr"
                                                                                                         UserId
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             OtherMemberUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "Membership updated"]
                                                                                                                ()))))))))))))))))))
                                    :<|> (Named
                                            "update-other-member"
                                            (Summary "Update membership of the specified user"
                                             :> (Description
                                                   "**Note**: at least one field has to be provided."
                                                 :> (MakesFederatedCall
                                                       'Galley "on-conversation-updated"
                                                     :> (MakesFederatedCall
                                                           'Galley "on-mls-message-sent"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'ConvMemberNotFound
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyOtherConversationMember)
                                                                                 :> (CanThrow
                                                                                       'InvalidTarget
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("members"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Target User ID"]
                                                                                                           "usr"
                                                                                                           UserId
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               OtherMemberUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  '[RespondEmpty
                                                                                                                      200
                                                                                                                      "Membership updated"]
                                                                                                                  ())))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name-deprecated"
                                                  (Summary "Update conversation name (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationName)
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationRename
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Name unchanged"
                                                                                                               "Name updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event)))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name-unqualified"
                                                        (Summary
                                                           "Update conversation name (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/name` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationName)
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("name"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   ConversationRename
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Name unchanged"
                                                                                                                         "Name updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-name"
                                                              (Summary "Update conversation name"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationName)
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (QualifiedCapture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("name"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ConversationRename
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    (UpdateResponses
                                                                                                                       "Name updated"
                                                                                                                       "Name unchanged"
                                                                                                                       Event)
                                                                                                                    (UpdateResult
                                                                                                                       Event))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-message-timer-unqualified"
                                                                    (Summary
                                                                       "Update the message timer for a conversation (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Brig
                                                                                           "get-users-by-ids"
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'ModifyConversationMessageTimer)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("message-timer"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   ConversationMessageTimerUpdate
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      (UpdateResponses
                                                                                                                                         "Message timer unchanged"
                                                                                                                                         "Message timer updated"
                                                                                                                                         Event)
                                                                                                                                      (UpdateResult
                                                                                                                                         Event)))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-message-timer"
                                                                          (Summary
                                                                             "Update the message timer for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationMessageTimer)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("message-timer"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationMessageTimerUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Message timer unchanged"
                                                                                                                                       "Message timer updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event)))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-receipt-mode-unqualified"
                                                                                (Summary
                                                                                   "Update receipt mode for a conversation (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "on-conversation-updated"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-mls-message-sent"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "update-conversation"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'ModifyConversationReceiptMode)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (Capture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("receipt-mode"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Receipt mode unchanged"
                                                                                                                                                         "Receipt mode updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-receipt-mode"
                                                                                      (Summary
                                                                                         "Update receipt mode for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Galley
                                                                                                     "update-conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Brig
                                                                                                         "get-users-by-ids"
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationReceiptMode)
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvAccessDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidOperation
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("receipt-mode"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                                       "Receipt mode updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access-unqualified"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation (deprecated)"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (Description
                                                                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'ModifyConversationAccess)
                                                                                                                             :> (CanThrow
                                                                                                                                   ('ActionDenied
                                                                                                                                      'RemoveConversationMember)
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvAccessDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'ConvNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidOperation
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'InvalidTargetAccess
                                                                                                                                                 :> ("conversations"
                                                                                                                                                     :> (Capture'
                                                                                                                                                           '[Description
                                                                                                                                                               "Conversation ID"]
                                                                                                                                                           "cnv"
                                                                                                                                                           ConvId
                                                                                                                                                         :> ("access"
                                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                                   'V2
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   ConversationAccessData
                                                                                                                                                                 :> MultiVerb
                                                                                                                                                                      'PUT
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (UpdateResponses
                                                                                                                                                                         "Access unchanged"
                                                                                                                                                                         "Access updated"
                                                                                                                                                                         Event)
                                                                                                                                                                      (UpdateResult
                                                                                                                                                                         Event)))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access@v2"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (Until
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationAccess)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("access"
                                                                                                                                                               :> (VersionedReqBody
                                                                                                                                                                     'V2
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                           "Access updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-access"
                                                                                                        (Summary
                                                                                                           "Update access modes for a conversation"
                                                                                                         :> (MakesFederatedCall
                                                                                                               'Galley
                                                                                                               "on-conversation-updated"
                                                                                                             :> (MakesFederatedCall
                                                                                                                   'Galley
                                                                                                                   "on-mls-message-sent"
                                                                                                                 :> (MakesFederatedCall
                                                                                                                       'Brig
                                                                                                                       "get-users-by-ids"
                                                                                                                     :> (From
                                                                                                                           'V3
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> (ZConn
                                                                                                                                 :> (CanThrow
                                                                                                                                       ('ActionDenied
                                                                                                                                          'ModifyConversationAccess)
                                                                                                                                     :> (CanThrow
                                                                                                                                           ('ActionDenied
                                                                                                                                              'RemoveConversationMember)
                                                                                                                                         :> (CanThrow
                                                                                                                                               'ConvAccessDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'ConvNotFound
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'InvalidOperation
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'InvalidTargetAccess
                                                                                                                                                         :> ("conversations"
                                                                                                                                                             :> (QualifiedCapture'
                                                                                                                                                                   '[Description
                                                                                                                                                                       "Conversation ID"]
                                                                                                                                                                   "cnv"
                                                                                                                                                                   ConvId
                                                                                                                                                                 :> ("access"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           ConversationAccessData
                                                                                                                                                                         :> MultiVerb
                                                                                                                                                                              'PUT
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (UpdateResponses
                                                                                                                                                                                 "Access unchanged"
                                                                                                                                                                                 "Access updated"
                                                                                                                                                                                 Event)
                                                                                                                                                                              (UpdateResult
                                                                                                                                                                                 Event))))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-conversation-self-unqualified"
                                                                                                              (Summary
                                                                                                                 "Get self membership properties (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("self"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (Maybe
                                                                                                                                           Member)))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-self-unqualified"
                                                                                                                    (Summary
                                                                                                                       "Update self membership properties (deprecated)"
                                                                                                                     :> (Deprecated
                                                                                                                         :> (Description
                                                                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvNotFound
                                                                                                                                 :> (ZLocalUser
                                                                                                                                     :> (ZConn
                                                                                                                                         :> ("conversations"
                                                                                                                                             :> (Capture'
                                                                                                                                                   '[Description
                                                                                                                                                       "Conversation ID"]
                                                                                                                                                   "cnv"
                                                                                                                                                   ConvId
                                                                                                                                                 :> ("self"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           MemberUpdate
                                                                                                                                                         :> MultiVerb
                                                                                                                                                              'PUT
                                                                                                                                                              '[JSON]
                                                                                                                                                              '[RespondEmpty
                                                                                                                                                                  200
                                                                                                                                                                  "Update successful"]
                                                                                                                                                              ()))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "update-conversation-self"
                                                                                                                          (Summary
                                                                                                                             "Update self membership properties"
                                                                                                                           :> (Description
                                                                                                                                 "**Note**: at least one field has to be provided."
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (ZLocalUser
                                                                                                                                       :> (ZConn
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (QualifiedCapture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("self"
                                                                                                                                                       :> (ReqBody
                                                                                                                                                             '[JSON]
                                                                                                                                                             MemberUpdate
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                '[RespondEmpty
                                                                                                                                                                    200
                                                                                                                                                                    "Update successful"]
                                                                                                                                                                ())))))))))
                                                                                                                        :<|> Named
                                                                                                                               "update-conversation-protocol"
                                                                                                                               (Summary
                                                                                                                                  "Update the protocol of the conversation"
                                                                                                                                :> (From
                                                                                                                                      'V5
                                                                                                                                    :> (Description
                                                                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                        :> (CanThrow
                                                                                                                                              'ConvNotFound
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'ConvInvalidProtocolTransition
                                                                                                                                                :> (CanThrow
                                                                                                                                                      ('ActionDenied
                                                                                                                                                         'LeaveConversation)
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'InvalidOperation
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      OperationDenied
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                        :> (ZLocalUser
                                                                                                                                                                            :> (ZConn
                                                                                                                                                                                :> ("conversations"
                                                                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                                                                          '[Description
                                                                                                                                                                                              "Conversation ID"]
                                                                                                                                                                                          "cnv"
                                                                                                                                                                                          ConvId
                                                                                                                                                                                        :> ("protocol"
                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                  ProtocolUpdate
                                                                                                                                                                                                :> MultiVerb
                                                                                                                                                                                                     'PUT
                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                                                                     (UpdateResult
                                                                                                                                                                                                        Event))))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"member-typing-unqualified" (((HasAnnotation 'Remote "galley" "update-typing-indicator",
  (HasAnnotation 'Remote "galley" "on-typing-indicator-updated",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> TypingStatus
 -> Sem
      '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "update-typing-indicator")
-> Dict
     (HasAnnotation 'Remote "galley" "on-typing-indicator-updated")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> TypingStatus
 -> Sem
      '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member NotificationSubsystem r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Input (Local ())) r, Member (Input UTCTime) r,
 Member MemberStore r, Member ConversationStore r,
 Member FederatorAccess r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> TypingStatus -> Sem r ()
memberTypingUnqualified))
    API
  (Named
     "member-typing-unqualified"
     (Summary "Sending typing notifications"
      :> (Until 'V3
          :> (MakesFederatedCall 'Galley "update-typing-indicator"
              :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                  :> (CanThrow 'ConvNotFound
                      :> (ZLocalUser
                          :> (ZConn
                              :> ("conversations"
                                  :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                      :> ("typing"
                                          :> (ReqBody '[JSON] TypingStatus
                                              :> MultiVerb
                                                   'POST
                                                   '[JSON]
                                                   '[RespondEmpty 200 "Notification sent"]
                                                   ()))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "member-typing-qualified"
        (Summary "Sending typing notifications"
         :> (MakesFederatedCall 'Galley "update-typing-indicator"
             :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                 :> (CanThrow 'ConvNotFound
                     :> (ZLocalUser
                         :> (ZConn
                             :> ("conversations"
                                 :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("typing"
                                         :> (ReqBody '[JSON] TypingStatus
                                             :> MultiVerb
                                                  'POST
                                                  '[JSON]
                                                  '[RespondEmpty 200 "Notification sent"]
                                                  ()))))))))))
      :<|> (Named
              "remove-member-unqualified"
              (Summary "Remove a member from a conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "leave-conversation"
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (Until 'V2
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("members"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Target User ID"]
                                                                         "usr"
                                                                         UserId
                                                                       :> RemoveFromConversationVerb)))))))))))))))
            :<|> (Named
                    "remove-member"
                    (Summary "Remove a member from a conversation"
                     :> (MakesFederatedCall 'Galley "leave-conversation"
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("members"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Target User ID"]
                                                                           "usr"
                                                                           UserId
                                                                         :> RemoveFromConversationVerb))))))))))))))
                  :<|> (Named
                          "update-other-member-unqualified"
                          (Summary "Update membership of the specified user (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'ConvMemberNotFound
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyOtherConversationMember)
                                                                   :> (CanThrow 'InvalidTarget
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("members"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Target User ID"]
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 OtherMemberUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "Membership updated"]
                                                                                                    ()))))))))))))))))))
                        :<|> (Named
                                "update-other-member"
                                (Summary "Update membership of the specified user"
                                 :> (Description "**Note**: at least one field has to be provided."
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'ConvMemberNotFound
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyOtherConversationMember)
                                                                     :> (CanThrow 'InvalidTarget
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("members"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Target User ID"]
                                                                                               "usr"
                                                                                               UserId
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   OtherMemberUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Membership updated"]
                                                                                                      ())))))))))))))))))
                              :<|> (Named
                                      "update-conversation-name-deprecated"
                                      (Summary "Update conversation name (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/name` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationName)
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationRename
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Name unchanged"
                                                                                                   "Name updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event)))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name-unqualified"
                                            (Summary "Update conversation name (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationName)
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("name"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       ConversationRename
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Name unchanged"
                                                                                                             "Name updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name"
                                                  (Summary "Update conversation name"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationName)
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("name"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ConversationRename
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        (UpdateResponses
                                                                                                           "Name updated"
                                                                                                           "Name unchanged"
                                                                                                           Event)
                                                                                                        (UpdateResult
                                                                                                           Event))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-message-timer-unqualified"
                                                        (Summary
                                                           "Update the message timer for a conversation (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'ModifyConversationMessageTimer)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("message-timer"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          (UpdateResponses
                                                                                                                             "Message timer unchanged"
                                                                                                                             "Message timer updated"
                                                                                                                             Event)
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-message-timer"
                                                              (Summary
                                                                 "Update the message timer for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationMessageTimer)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("message-timer"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Message timer unchanged"
                                                                                                                           "Message timer updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event)))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-receipt-mode-unqualified"
                                                                    (Summary
                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "update-conversation"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationReceiptMode)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("receipt-mode"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                             "Receipt mode updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-receipt-mode"
                                                                          (Summary
                                                                             "Update receipt mode for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "update-conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationReceiptMode)
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("receipt-mode"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                           "Receipt mode updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access-unqualified"
                                                                                (Summary
                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (Description
                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'ModifyConversationAccess)
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'RemoveConversationMember)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidTargetAccess
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("access"
                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                       'V2
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationAccessData
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Access unchanged"
                                                                                                                                                             "Access updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event)))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access@v2"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationAccess)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidTargetAccess
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("access"
                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                         'V2
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationAccessData
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Access unchanged"
                                                                                                                                                               "Access updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (From
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationAccess)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidTargetAccess
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("access"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationAccessData
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                     "Access updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-conversation-self-unqualified"
                                                                                                  (Summary
                                                                                                     "Get self membership properties (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("self"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (Maybe
                                                                                                                               Member)))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-self-unqualified"
                                                                                                        (Summary
                                                                                                           "Update self membership properties (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("self"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               MemberUpdate
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "Update successful"]
                                                                                                                                                  ()))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-self"
                                                                                                              (Summary
                                                                                                                 "Update self membership properties"
                                                                                                               :> (Description
                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("self"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 MemberUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[RespondEmpty
                                                                                                                                                        200
                                                                                                                                                        "Update successful"]
                                                                                                                                                    ())))))))))
                                                                                                            :<|> Named
                                                                                                                   "update-conversation-protocol"
                                                                                                                   (Summary
                                                                                                                      "Update the protocol of the conversation"
                                                                                                                    :> (From
                                                                                                                          'V5
                                                                                                                        :> (Description
                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                            :> (CanThrow
                                                                                                                                  'ConvNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                    :> (CanThrow
                                                                                                                                          ('ActionDenied
                                                                                                                                             'LeaveConversation)
                                                                                                                                        :> (CanThrow
                                                                                                                                              'InvalidOperation
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'NotATeamMember
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'TeamNotFound
                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                :> (ZConn
                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                              '[Description
                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                              "cnv"
                                                                                                                                                                              ConvId
                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                         'PUT
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "member-typing-unqualified"
        (Summary "Sending typing notifications"
         :> (Until 'V3
             :> (MakesFederatedCall 'Galley "update-typing-indicator"
                 :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                     :> (CanThrow 'ConvNotFound
                         :> (ZLocalUser
                             :> (ZConn
                                 :> ("conversations"
                                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                         :> ("typing"
                                             :> (ReqBody '[JSON] TypingStatus
                                                 :> MultiVerb
                                                      'POST
                                                      '[JSON]
                                                      '[RespondEmpty 200 "Notification sent"]
                                                      ())))))))))))
      :<|> (Named
              "member-typing-qualified"
              (Summary "Sending typing notifications"
               :> (MakesFederatedCall 'Galley "update-typing-indicator"
                   :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                       :> (CanThrow 'ConvNotFound
                           :> (ZLocalUser
                               :> (ZConn
                                   :> ("conversations"
                                       :> (QualifiedCapture'
                                             '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("typing"
                                               :> (ReqBody '[JSON] TypingStatus
                                                   :> MultiVerb
                                                        'POST
                                                        '[JSON]
                                                        '[RespondEmpty 200 "Notification sent"]
                                                        ()))))))))))
            :<|> (Named
                    "remove-member-unqualified"
                    (Summary "Remove a member from a conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "leave-conversation"
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (Until 'V2
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("members"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Target User ID"]
                                                                               "usr"
                                                                               UserId
                                                                             :> RemoveFromConversationVerb)))))))))))))))
                  :<|> (Named
                          "remove-member"
                          (Summary "Remove a member from a conversation"
                           :> (MakesFederatedCall 'Galley "leave-conversation"
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'RemoveConversationMember)
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("members"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Target User ID"]
                                                                                 "usr"
                                                                                 UserId
                                                                               :> RemoveFromConversationVerb))))))))))))))
                        :<|> (Named
                                "update-other-member-unqualified"
                                (Summary "Update membership of the specified user (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'ConvMemberNotFound
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyOtherConversationMember)
                                                                         :> (CanThrow 'InvalidTarget
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("members"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Target User ID"]
                                                                                                   "usr"
                                                                                                   UserId
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       OtherMemberUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "Membership updated"]
                                                                                                          ()))))))))))))))))))
                              :<|> (Named
                                      "update-other-member"
                                      (Summary "Update membership of the specified user"
                                       :> (Description
                                             "**Note**: at least one field has to be provided."
                                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'ConvMemberNotFound
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyOtherConversationMember)
                                                                           :> (CanThrow
                                                                                 'InvalidTarget
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("members"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Target User ID"]
                                                                                                     "usr"
                                                                                                     UserId
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         OtherMemberUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            '[RespondEmpty
                                                                                                                200
                                                                                                                "Membership updated"]
                                                                                                            ())))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name-deprecated"
                                            (Summary "Update conversation name (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationName)
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationRename
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Name unchanged"
                                                                                                         "Name updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event)))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name-unqualified"
                                                  (Summary "Update conversation name (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/name` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationName)
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("name"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             ConversationRename
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Name unchanged"
                                                                                                                   "Name updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-name"
                                                        (Summary "Update conversation name"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationName)
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (QualifiedCapture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("name"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ConversationRename
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              (UpdateResponses
                                                                                                                 "Name updated"
                                                                                                                 "Name unchanged"
                                                                                                                 Event)
                                                                                                              (UpdateResult
                                                                                                                 Event))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-message-timer-unqualified"
                                                              (Summary
                                                                 "Update the message timer for a conversation (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Brig
                                                                                     "get-users-by-ids"
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'ModifyConversationMessageTimer)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("message-timer"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             ConversationMessageTimerUpdate
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                (UpdateResponses
                                                                                                                                   "Message timer unchanged"
                                                                                                                                   "Message timer updated"
                                                                                                                                   Event)
                                                                                                                                (UpdateResult
                                                                                                                                   Event)))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-message-timer"
                                                                    (Summary
                                                                       "Update the message timer for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationMessageTimer)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("message-timer"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationMessageTimerUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Message timer unchanged"
                                                                                                                                 "Message timer updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event)))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-receipt-mode-unqualified"
                                                                          (Summary
                                                                             "Update receipt mode for a conversation (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "on-conversation-updated"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-mls-message-sent"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "update-conversation"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'ModifyConversationReceiptMode)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> ("conversations"
                                                                                                                               :> (Capture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("receipt-mode"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationReceiptModeUpdate
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Receipt mode unchanged"
                                                                                                                                                   "Receipt mode updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-receipt-mode"
                                                                                (Summary
                                                                                   "Update receipt mode for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Galley
                                                                                               "update-conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Brig
                                                                                                   "get-users-by-ids"
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationReceiptMode)
                                                                                                             :> (CanThrow
                                                                                                                   'ConvAccessDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidOperation
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("receipt-mode"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                                 "Receipt mode updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access-unqualified"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation (deprecated)"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (Description
                                                                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'ModifyConversationAccess)
                                                                                                                       :> (CanThrow
                                                                                                                             ('ActionDenied
                                                                                                                                'RemoveConversationMember)
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvAccessDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'ConvNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidOperation
                                                                                                                                       :> (CanThrow
                                                                                                                                             'InvalidTargetAccess
                                                                                                                                           :> ("conversations"
                                                                                                                                               :> (Capture'
                                                                                                                                                     '[Description
                                                                                                                                                         "Conversation ID"]
                                                                                                                                                     "cnv"
                                                                                                                                                     ConvId
                                                                                                                                                   :> ("access"
                                                                                                                                                       :> (VersionedReqBody
                                                                                                                                                             'V2
                                                                                                                                                             '[JSON]
                                                                                                                                                             ConversationAccessData
                                                                                                                                                           :> MultiVerb
                                                                                                                                                                'PUT
                                                                                                                                                                '[JSON]
                                                                                                                                                                (UpdateResponses
                                                                                                                                                                   "Access unchanged"
                                                                                                                                                                   "Access updated"
                                                                                                                                                                   Event)
                                                                                                                                                                (UpdateResult
                                                                                                                                                                   Event)))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access@v2"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (Until
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationAccess)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidTargetAccess
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("access"
                                                                                                                                                         :> (VersionedReqBody
                                                                                                                                                               'V2
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationAccessData
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                     "Access updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-access"
                                                                                                  (Summary
                                                                                                     "Update access modes for a conversation"
                                                                                                   :> (MakesFederatedCall
                                                                                                         'Galley
                                                                                                         "on-conversation-updated"
                                                                                                       :> (MakesFederatedCall
                                                                                                             'Galley
                                                                                                             "on-mls-message-sent"
                                                                                                           :> (MakesFederatedCall
                                                                                                                 'Brig
                                                                                                                 "get-users-by-ids"
                                                                                                               :> (From
                                                                                                                     'V3
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> (ZConn
                                                                                                                           :> (CanThrow
                                                                                                                                 ('ActionDenied
                                                                                                                                    'ModifyConversationAccess)
                                                                                                                               :> (CanThrow
                                                                                                                                     ('ActionDenied
                                                                                                                                        'RemoveConversationMember)
                                                                                                                                   :> (CanThrow
                                                                                                                                         'ConvAccessDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'ConvNotFound
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'InvalidOperation
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'InvalidTargetAccess
                                                                                                                                                   :> ("conversations"
                                                                                                                                                       :> (QualifiedCapture'
                                                                                                                                                             '[Description
                                                                                                                                                                 "Conversation ID"]
                                                                                                                                                             "cnv"
                                                                                                                                                             ConvId
                                                                                                                                                           :> ("access"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     ConversationAccessData
                                                                                                                                                                   :> MultiVerb
                                                                                                                                                                        'PUT
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (UpdateResponses
                                                                                                                                                                           "Access unchanged"
                                                                                                                                                                           "Access updated"
                                                                                                                                                                           Event)
                                                                                                                                                                        (UpdateResult
                                                                                                                                                                           Event))))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-conversation-self-unqualified"
                                                                                                        (Summary
                                                                                                           "Get self membership properties (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("self"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (Maybe
                                                                                                                                     Member)))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-self-unqualified"
                                                                                                              (Summary
                                                                                                                 "Update self membership properties (deprecated)"
                                                                                                               :> (Deprecated
                                                                                                                   :> (Description
                                                                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvNotFound
                                                                                                                           :> (ZLocalUser
                                                                                                                               :> (ZConn
                                                                                                                                   :> ("conversations"
                                                                                                                                       :> (Capture'
                                                                                                                                             '[Description
                                                                                                                                                 "Conversation ID"]
                                                                                                                                             "cnv"
                                                                                                                                             ConvId
                                                                                                                                           :> ("self"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     MemberUpdate
                                                                                                                                                   :> MultiVerb
                                                                                                                                                        'PUT
                                                                                                                                                        '[JSON]
                                                                                                                                                        '[RespondEmpty
                                                                                                                                                            200
                                                                                                                                                            "Update successful"]
                                                                                                                                                        ()))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "update-conversation-self"
                                                                                                                    (Summary
                                                                                                                       "Update self membership properties"
                                                                                                                     :> (Description
                                                                                                                           "**Note**: at least one field has to be provided."
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (ZLocalUser
                                                                                                                                 :> (ZConn
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (QualifiedCapture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("self"
                                                                                                                                                 :> (ReqBody
                                                                                                                                                       '[JSON]
                                                                                                                                                       MemberUpdate
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          '[RespondEmpty
                                                                                                                                                              200
                                                                                                                                                              "Update successful"]
                                                                                                                                                          ())))))))))
                                                                                                                  :<|> Named
                                                                                                                         "update-conversation-protocol"
                                                                                                                         (Summary
                                                                                                                            "Update the protocol of the conversation"
                                                                                                                          :> (From
                                                                                                                                'V5
                                                                                                                              :> (Description
                                                                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                                  :> (CanThrow
                                                                                                                                        'ConvNotFound
                                                                                                                                      :> (CanThrow
                                                                                                                                            'ConvInvalidProtocolTransition
                                                                                                                                          :> (CanThrow
                                                                                                                                                ('ActionDenied
                                                                                                                                                   'LeaveConversation)
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'InvalidOperation
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'NotATeamMember
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                OperationDenied
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                  :> (ZLocalUser
                                                                                                                                                                      :> (ZConn
                                                                                                                                                                          :> ("conversations"
                                                                                                                                                                              :> (QualifiedCapture'
                                                                                                                                                                                    '[Description
                                                                                                                                                                                        "Conversation ID"]
                                                                                                                                                                                    "cnv"
                                                                                                                                                                                    ConvId
                                                                                                                                                                                  :> ("protocol"
                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                            ProtocolUpdate
                                                                                                                                                                                          :> MultiVerb
                                                                                                                                                                                               'PUT
                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                               ConvUpdateResponses
                                                                                                                                                                                               (UpdateResult
                                                                                                                                                                                                  Event)))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"member-typing-qualified" (((HasAnnotation 'Remote "galley" "update-typing-indicator",
  (HasAnnotation 'Remote "galley" "on-typing-indicator-updated",
   () :: Constraint)) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> TypingStatus
 -> Sem
      '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "update-typing-indicator")
-> Dict
     (HasAnnotation 'Remote "galley" "on-typing-indicator-updated")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> TypingStatus
 -> Sem
      '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> TypingStatus
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member NotificationSubsystem r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Input (Local ())) r, Member (Input UTCTime) r,
 Member ConversationStore r, Member MemberStore r,
 Member FederatorAccess r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> Qualified ConvId -> TypingStatus -> Sem r ()
memberTyping))
    API
  (Named
     "member-typing-qualified"
     (Summary "Sending typing notifications"
      :> (MakesFederatedCall 'Galley "update-typing-indicator"
          :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
              :> (CanThrow 'ConvNotFound
                  :> (ZLocalUser
                      :> (ZConn
                          :> ("conversations"
                              :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                  :> ("typing"
                                      :> (ReqBody '[JSON] TypingStatus
                                          :> MultiVerb
                                               'POST
                                               '[JSON]
                                               '[RespondEmpty 200 "Notification sent"]
                                               ())))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "remove-member-unqualified"
        (Summary "Remove a member from a conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "leave-conversation"
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (Until 'V2
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("members"
                                                             :> (Capture'
                                                                   '[Description "Target User ID"]
                                                                   "usr"
                                                                   UserId
                                                                 :> RemoveFromConversationVerb)))))))))))))))
      :<|> (Named
              "remove-member"
              (Summary "Remove a member from a conversation"
               :> (MakesFederatedCall 'Galley "leave-conversation"
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> ("conversations"
                                                       :> (QualifiedCapture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("members"
                                                               :> (QualifiedCapture'
                                                                     '[Description "Target User ID"]
                                                                     "usr"
                                                                     UserId
                                                                   :> RemoveFromConversationVerb))))))))))))))
            :<|> (Named
                    "update-other-member-unqualified"
                    (Summary "Update membership of the specified user (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'ConvMemberNotFound
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyOtherConversationMember)
                                                             :> (CanThrow 'InvalidTarget
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("members"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Target User ID"]
                                                                                       "usr"
                                                                                       UserId
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           OtherMemberUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "Membership updated"]
                                                                                              ()))))))))))))))))))
                  :<|> (Named
                          "update-other-member"
                          (Summary "Update membership of the specified user"
                           :> (Description "**Note**: at least one field has to be provided."
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'ConvMemberNotFound
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyOtherConversationMember)
                                                               :> (CanThrow 'InvalidTarget
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("members"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Target User ID"]
                                                                                         "usr"
                                                                                         UserId
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             OtherMemberUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Membership updated"]
                                                                                                ())))))))))))))))))
                        :<|> (Named
                                "update-conversation-name-deprecated"
                                (Summary "Update conversation name (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/name` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (CanThrow
                                                           ('ActionDenied 'ModifyConversationName)
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationRename
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Name unchanged"
                                                                                             "Name updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event)))))))))))))))
                              :<|> (Named
                                      "update-conversation-name-unqualified"
                                      (Summary "Update conversation name (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/name` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationName)
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("name"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 ConversationRename
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Name unchanged"
                                                                                                       "Name updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name"
                                            (Summary "Update conversation name"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationName)
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("name"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ConversationRename
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  (UpdateResponses
                                                                                                     "Name updated"
                                                                                                     "Name unchanged"
                                                                                                     Event)
                                                                                                  (UpdateResult
                                                                                                     Event))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-message-timer-unqualified"
                                                  (Summary
                                                     "Update the message timer for a conversation (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'ModifyConversationMessageTimer)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("message-timer"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ConversationMessageTimerUpdate
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    (UpdateResponses
                                                                                                                       "Message timer unchanged"
                                                                                                                       "Message timer updated"
                                                                                                                       Event)
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-message-timer"
                                                        (Summary
                                                           "Update the message timer for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationMessageTimer)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("message-timer"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationMessageTimerUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Message timer unchanged"
                                                                                                                     "Message timer updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event)))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-receipt-mode-unqualified"
                                                              (Summary
                                                                 "Update receipt mode for a conversation (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "update-conversation"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationReceiptMode)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("receipt-mode"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                       "Receipt mode updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-receipt-mode"
                                                                    (Summary
                                                                       "Update receipt mode for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "update-conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationReceiptMode)
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("receipt-mode"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                     "Receipt mode updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access-unqualified"
                                                                          (Summary
                                                                             "Update access modes for a conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (Until 'V3
                                                                                           :> (Description
                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'ModifyConversationAccess)
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'RemoveConversationMember)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidTargetAccess
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("access"
                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                 'V2
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationAccessData
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Access unchanged"
                                                                                                                                                       "Access updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event)))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access@v2"
                                                                                (Summary
                                                                                   "Update access modes for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationAccess)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidTargetAccess
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("access"
                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                   'V2
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationAccessData
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Access unchanged"
                                                                                                                                                         "Access updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (From
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationAccess)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidTargetAccess
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("access"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationAccessData
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Access unchanged"
                                                                                                                                                               "Access updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-self-unqualified"
                                                                                            (Summary
                                                                                               "Get self membership properties (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("self"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (Maybe
                                                                                                                         Member)))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-self-unqualified"
                                                                                                  (Summary
                                                                                                     "Update self membership properties (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("self"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         MemberUpdate
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "Update successful"]
                                                                                                                                            ()))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-self"
                                                                                                        (Summary
                                                                                                           "Update self membership properties"
                                                                                                         :> (Description
                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("self"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           MemberUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              '[RespondEmpty
                                                                                                                                                  200
                                                                                                                                                  "Update successful"]
                                                                                                                                              ())))))))))
                                                                                                      :<|> Named
                                                                                                             "update-conversation-protocol"
                                                                                                             (Summary
                                                                                                                "Update the protocol of the conversation"
                                                                                                              :> (From
                                                                                                                    'V5
                                                                                                                  :> (Description
                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                      :> (CanThrow
                                                                                                                            'ConvNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                              :> (CanThrow
                                                                                                                                    ('ActionDenied
                                                                                                                                       'LeaveConversation)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'InvalidOperation
                                                                                                                                      :> (CanThrow
                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'NotATeamMember
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'TeamNotFound
                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                          :> (ZConn
                                                                                                                                                              :> ("conversations"
                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                        '[Description
                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                        "cnv"
                                                                                                                                                                        ConvId
                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                   'PUT
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "member-typing-qualified"
        (Summary "Sending typing notifications"
         :> (MakesFederatedCall 'Galley "update-typing-indicator"
             :> (MakesFederatedCall 'Galley "on-typing-indicator-updated"
                 :> (CanThrow 'ConvNotFound
                     :> (ZLocalUser
                         :> (ZConn
                             :> ("conversations"
                                 :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("typing"
                                         :> (ReqBody '[JSON] TypingStatus
                                             :> MultiVerb
                                                  'POST
                                                  '[JSON]
                                                  '[RespondEmpty 200 "Notification sent"]
                                                  ()))))))))))
      :<|> (Named
              "remove-member-unqualified"
              (Summary "Remove a member from a conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "leave-conversation"
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (Until 'V2
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("members"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Target User ID"]
                                                                         "usr"
                                                                         UserId
                                                                       :> RemoveFromConversationVerb)))))))))))))))
            :<|> (Named
                    "remove-member"
                    (Summary "Remove a member from a conversation"
                     :> (MakesFederatedCall 'Galley "leave-conversation"
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("members"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Target User ID"]
                                                                           "usr"
                                                                           UserId
                                                                         :> RemoveFromConversationVerb))))))))))))))
                  :<|> (Named
                          "update-other-member-unqualified"
                          (Summary "Update membership of the specified user (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'ConvMemberNotFound
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyOtherConversationMember)
                                                                   :> (CanThrow 'InvalidTarget
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("members"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Target User ID"]
                                                                                             "usr"
                                                                                             UserId
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 OtherMemberUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "Membership updated"]
                                                                                                    ()))))))))))))))))))
                        :<|> (Named
                                "update-other-member"
                                (Summary "Update membership of the specified user"
                                 :> (Description "**Note**: at least one field has to be provided."
                                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'ConvMemberNotFound
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyOtherConversationMember)
                                                                     :> (CanThrow 'InvalidTarget
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("members"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Target User ID"]
                                                                                               "usr"
                                                                                               UserId
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   OtherMemberUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      '[RespondEmpty
                                                                                                          200
                                                                                                          "Membership updated"]
                                                                                                      ())))))))))))))))))
                              :<|> (Named
                                      "update-conversation-name-deprecated"
                                      (Summary "Update conversation name (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/name` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationName)
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationRename
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Name unchanged"
                                                                                                   "Name updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event)))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name-unqualified"
                                            (Summary "Update conversation name (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/name` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationName)
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("name"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       ConversationRename
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Name unchanged"
                                                                                                             "Name updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-name"
                                                  (Summary "Update conversation name"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationName)
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (QualifiedCapture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("name"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ConversationRename
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        (UpdateResponses
                                                                                                           "Name updated"
                                                                                                           "Name unchanged"
                                                                                                           Event)
                                                                                                        (UpdateResult
                                                                                                           Event))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-message-timer-unqualified"
                                                        (Summary
                                                           "Update the message timer for a conversation (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Brig
                                                                               "get-users-by-ids"
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'ModifyConversationMessageTimer)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("message-timer"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       ConversationMessageTimerUpdate
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          (UpdateResponses
                                                                                                                             "Message timer unchanged"
                                                                                                                             "Message timer updated"
                                                                                                                             Event)
                                                                                                                          (UpdateResult
                                                                                                                             Event)))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-message-timer"
                                                              (Summary
                                                                 "Update the message timer for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationMessageTimer)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("message-timer"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationMessageTimerUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Message timer unchanged"
                                                                                                                           "Message timer updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event)))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-receipt-mode-unqualified"
                                                                    (Summary
                                                                       "Update receipt mode for a conversation (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "on-conversation-updated"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-mls-message-sent"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "update-conversation"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'ModifyConversationReceiptMode)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> ("conversations"
                                                                                                                         :> (Capture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("receipt-mode"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationReceiptModeUpdate
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Receipt mode unchanged"
                                                                                                                                             "Receipt mode updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-receipt-mode"
                                                                          (Summary
                                                                             "Update receipt mode for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Galley
                                                                                         "update-conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Brig
                                                                                             "get-users-by-ids"
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationReceiptMode)
                                                                                                       :> (CanThrow
                                                                                                             'ConvAccessDenied
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidOperation
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("receipt-mode"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Receipt mode unchanged"
                                                                                                                                           "Receipt mode updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access-unqualified"
                                                                                (Summary
                                                                                   "Update access modes for a conversation (deprecated)"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (Description
                                                                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'ModifyConversationAccess)
                                                                                                                 :> (CanThrow
                                                                                                                       ('ActionDenied
                                                                                                                          'RemoveConversationMember)
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvAccessDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'ConvNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidOperation
                                                                                                                                 :> (CanThrow
                                                                                                                                       'InvalidTargetAccess
                                                                                                                                     :> ("conversations"
                                                                                                                                         :> (Capture'
                                                                                                                                               '[Description
                                                                                                                                                   "Conversation ID"]
                                                                                                                                               "cnv"
                                                                                                                                               ConvId
                                                                                                                                             :> ("access"
                                                                                                                                                 :> (VersionedReqBody
                                                                                                                                                       'V2
                                                                                                                                                       '[JSON]
                                                                                                                                                       ConversationAccessData
                                                                                                                                                     :> MultiVerb
                                                                                                                                                          'PUT
                                                                                                                                                          '[JSON]
                                                                                                                                                          (UpdateResponses
                                                                                                                                                             "Access unchanged"
                                                                                                                                                             "Access updated"
                                                                                                                                                             Event)
                                                                                                                                                          (UpdateResult
                                                                                                                                                             Event)))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access@v2"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (Until
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationAccess)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidTargetAccess
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("access"
                                                                                                                                                   :> (VersionedReqBody
                                                                                                                                                         'V2
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationAccessData
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Access unchanged"
                                                                                                                                                               "Access updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-access"
                                                                                            (Summary
                                                                                               "Update access modes for a conversation"
                                                                                             :> (MakesFederatedCall
                                                                                                   'Galley
                                                                                                   "on-conversation-updated"
                                                                                                 :> (MakesFederatedCall
                                                                                                       'Galley
                                                                                                       "on-mls-message-sent"
                                                                                                     :> (MakesFederatedCall
                                                                                                           'Brig
                                                                                                           "get-users-by-ids"
                                                                                                         :> (From
                                                                                                               'V3
                                                                                                             :> (ZLocalUser
                                                                                                                 :> (ZConn
                                                                                                                     :> (CanThrow
                                                                                                                           ('ActionDenied
                                                                                                                              'ModifyConversationAccess)
                                                                                                                         :> (CanThrow
                                                                                                                               ('ActionDenied
                                                                                                                                  'RemoveConversationMember)
                                                                                                                             :> (CanThrow
                                                                                                                                   'ConvAccessDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'ConvNotFound
                                                                                                                                     :> (CanThrow
                                                                                                                                           'InvalidOperation
                                                                                                                                         :> (CanThrow
                                                                                                                                               'InvalidTargetAccess
                                                                                                                                             :> ("conversations"
                                                                                                                                                 :> (QualifiedCapture'
                                                                                                                                                       '[Description
                                                                                                                                                           "Conversation ID"]
                                                                                                                                                       "cnv"
                                                                                                                                                       ConvId
                                                                                                                                                     :> ("access"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               ConversationAccessData
                                                                                                                                                             :> MultiVerb
                                                                                                                                                                  'PUT
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (UpdateResponses
                                                                                                                                                                     "Access unchanged"
                                                                                                                                                                     "Access updated"
                                                                                                                                                                     Event)
                                                                                                                                                                  (UpdateResult
                                                                                                                                                                     Event))))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-conversation-self-unqualified"
                                                                                                  (Summary
                                                                                                     "Get self membership properties (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("self"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (Maybe
                                                                                                                               Member)))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-self-unqualified"
                                                                                                        (Summary
                                                                                                           "Update self membership properties (deprecated)"
                                                                                                         :> (Deprecated
                                                                                                             :> (Description
                                                                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvNotFound
                                                                                                                     :> (ZLocalUser
                                                                                                                         :> (ZConn
                                                                                                                             :> ("conversations"
                                                                                                                                 :> (Capture'
                                                                                                                                       '[Description
                                                                                                                                           "Conversation ID"]
                                                                                                                                       "cnv"
                                                                                                                                       ConvId
                                                                                                                                     :> ("self"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               MemberUpdate
                                                                                                                                             :> MultiVerb
                                                                                                                                                  'PUT
                                                                                                                                                  '[JSON]
                                                                                                                                                  '[RespondEmpty
                                                                                                                                                      200
                                                                                                                                                      "Update successful"]
                                                                                                                                                  ()))))))))))
                                                                                                      :<|> (Named
                                                                                                              "update-conversation-self"
                                                                                                              (Summary
                                                                                                                 "Update self membership properties"
                                                                                                               :> (Description
                                                                                                                     "**Note**: at least one field has to be provided."
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (ZLocalUser
                                                                                                                           :> (ZConn
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (QualifiedCapture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("self"
                                                                                                                                           :> (ReqBody
                                                                                                                                                 '[JSON]
                                                                                                                                                 MemberUpdate
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    '[RespondEmpty
                                                                                                                                                        200
                                                                                                                                                        "Update successful"]
                                                                                                                                                    ())))))))))
                                                                                                            :<|> Named
                                                                                                                   "update-conversation-protocol"
                                                                                                                   (Summary
                                                                                                                      "Update the protocol of the conversation"
                                                                                                                    :> (From
                                                                                                                          'V5
                                                                                                                        :> (Description
                                                                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                            :> (CanThrow
                                                                                                                                  'ConvNotFound
                                                                                                                                :> (CanThrow
                                                                                                                                      'ConvInvalidProtocolTransition
                                                                                                                                    :> (CanThrow
                                                                                                                                          ('ActionDenied
                                                                                                                                             'LeaveConversation)
                                                                                                                                        :> (CanThrow
                                                                                                                                              'InvalidOperation
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'NotATeamMember
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'TeamNotFound
                                                                                                                                                            :> (ZLocalUser
                                                                                                                                                                :> (ZConn
                                                                                                                                                                    :> ("conversations"
                                                                                                                                                                        :> (QualifiedCapture'
                                                                                                                                                                              '[Description
                                                                                                                                                                                  "Conversation ID"]
                                                                                                                                                                              "cnv"
                                                                                                                                                                              ConvId
                                                                                                                                                                            :> ("protocol"
                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                      ProtocolUpdate
                                                                                                                                                                                    :> MultiVerb
                                                                                                                                                                                         'PUT
                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                         ConvUpdateResponses
                                                                                                                                                                                         (UpdateResult
                                                                                                                                                                                            Event))))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"remove-member-unqualified" (((HasAnnotation 'Remote "galley" "leave-conversation",
  (HasAnnotation 'Remote "galley" "on-conversation-updated",
   (HasAnnotation 'Remote "galley" "on-mls-message-sent",
    (HasAnnotation 'Remote "brig" "get-users-by-ids",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> UserId
 -> Sem
      '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (Maybe Event))
-> Dict (HasAnnotation 'Remote "galley" "leave-conversation")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> UserId
 -> Sem
      '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (Maybe Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'RemoveConversationMember) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input Env) r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member ProposalStore r, Member Random r,
 Member SubConversationStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> UserId -> Sem r (Maybe Event)
removeMemberUnqualified))
    API
  (Named
     "remove-member-unqualified"
     (Summary "Remove a member from a conversation (deprecated)"
      :> (MakesFederatedCall 'Galley "leave-conversation"
          :> (MakesFederatedCall 'Galley "on-conversation-updated"
              :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                  :> (MakesFederatedCall 'Brig "get-users-by-ids"
                      :> (Until 'V2
                          :> (ZLocalUser
                              :> (ZConn
                                  :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                      :> (CanThrow 'ConvNotFound
                                          :> (CanThrow 'InvalidOperation
                                              :> ("conversations"
                                                  :> (Capture'
                                                        '[Description "Conversation ID"]
                                                        "cnv"
                                                        ConvId
                                                      :> ("members"
                                                          :> (Capture'
                                                                '[Description "Target User ID"]
                                                                "usr"
                                                                UserId
                                                              :> RemoveFromConversationVerb))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "remove-member"
        (Summary "Remove a member from a conversation"
         :> (MakesFederatedCall 'Galley "leave-conversation"
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> ("conversations"
                                                 :> (QualifiedCapture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("members"
                                                         :> (QualifiedCapture'
                                                               '[Description "Target User ID"]
                                                               "usr"
                                                               UserId
                                                             :> RemoveFromConversationVerb))))))))))))))
      :<|> (Named
              "update-other-member-unqualified"
              (Summary "Update membership of the specified user (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'ConvMemberNotFound
                                                   :> (CanThrow
                                                         ('ActionDenied
                                                            'ModifyOtherConversationMember)
                                                       :> (CanThrow 'InvalidTarget
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("members"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Target User ID"]
                                                                                 "usr"
                                                                                 UserId
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     OtherMemberUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "Membership updated"]
                                                                                        ()))))))))))))))))))
            :<|> (Named
                    "update-other-member"
                    (Summary "Update membership of the specified user"
                     :> (Description "**Note**: at least one field has to be provided."
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'ConvMemberNotFound
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyOtherConversationMember)
                                                         :> (CanThrow 'InvalidTarget
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("members"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Target User ID"]
                                                                                   "usr"
                                                                                   UserId
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       OtherMemberUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Membership updated"]
                                                                                          ())))))))))))))))))
                  :<|> (Named
                          "update-conversation-name-deprecated"
                          (Summary "Update conversation name (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/name` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationRename
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Name unchanged"
                                                                                       "Name updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event)))))))))))))))
                        :<|> (Named
                                "update-conversation-name-unqualified"
                                (Summary "Update conversation name (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/name` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (CanThrow
                                                           ('ActionDenied 'ModifyConversationName)
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("name"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           ConversationRename
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Name unchanged"
                                                                                                 "Name updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))
                              :<|> (Named
                                      "update-conversation-name"
                                      (Summary "Update conversation name"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationName)
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("name"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ConversationRename
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            (UpdateResponses
                                                                                               "Name updated"
                                                                                               "Name unchanged"
                                                                                               Event)
                                                                                            (UpdateResult
                                                                                               Event))))))))))))))
                                    :<|> (Named
                                            "update-conversation-message-timer-unqualified"
                                            (Summary
                                               "Update the message timer for a conversation (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'ModifyConversationMessageTimer)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("message-timer"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ConversationMessageTimerUpdate
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              (UpdateResponses
                                                                                                                 "Message timer unchanged"
                                                                                                                 "Message timer updated"
                                                                                                                 Event)
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-message-timer"
                                                  (Summary
                                                     "Update the message timer for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationMessageTimer)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("message-timer"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationMessageTimerUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Message timer unchanged"
                                                                                                               "Message timer updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event)))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-receipt-mode-unqualified"
                                                        (Summary
                                                           "Update receipt mode for a conversation (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "update-conversation"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationReceiptMode)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("receipt-mode"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                 "Receipt mode updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-receipt-mode"
                                                              (Summary
                                                                 "Update receipt mode for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "update-conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationReceiptMode)
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("receipt-mode"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Receipt mode unchanged"
                                                                                                                               "Receipt mode updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access-unqualified"
                                                                    (Summary
                                                                       "Update access modes for a conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (Until 'V3
                                                                                     :> (Description
                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'ModifyConversationAccess)
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'RemoveConversationMember)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidTargetAccess
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("access"
                                                                                                                                     :> (VersionedReqBody
                                                                                                                                           'V2
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationAccessData
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Access unchanged"
                                                                                                                                                 "Access updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event)))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access@v2"
                                                                          (Summary
                                                                             "Update access modes for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (Until 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationAccess)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidTargetAccess
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("access"
                                                                                                                                       :> (VersionedReqBody
                                                                                                                                             'V2
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationAccessData
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Access unchanged"
                                                                                                                                                   "Access updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access"
                                                                                (Summary
                                                                                   "Update access modes for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (From
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationAccess)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidTargetAccess
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("access"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationAccessData
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Access unchanged"
                                                                                                                                                         "Access updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-self-unqualified"
                                                                                      (Summary
                                                                                         "Get self membership properties (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("self"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (Maybe
                                                                                                                   Member)))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-self-unqualified"
                                                                                            (Summary
                                                                                               "Update self membership properties (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("self"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   MemberUpdate
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "Update successful"]
                                                                                                                                      ()))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-self"
                                                                                                  (Summary
                                                                                                     "Update self membership properties"
                                                                                                   :> (Description
                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("self"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     MemberUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        '[RespondEmpty
                                                                                                                                            200
                                                                                                                                            "Update successful"]
                                                                                                                                        ())))))))))
                                                                                                :<|> Named
                                                                                                       "update-conversation-protocol"
                                                                                                       (Summary
                                                                                                          "Update the protocol of the conversation"
                                                                                                        :> (From
                                                                                                              'V5
                                                                                                            :> (Description
                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                :> (CanThrow
                                                                                                                      'ConvNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                        :> (CanThrow
                                                                                                                              ('ActionDenied
                                                                                                                                 'LeaveConversation)
                                                                                                                            :> (CanThrow
                                                                                                                                  'InvalidOperation
                                                                                                                                :> (CanThrow
                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'NotATeamMember
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'TeamNotFound
                                                                                                                                                :> (ZLocalUser
                                                                                                                                                    :> (ZConn
                                                                                                                                                        :> ("conversations"
                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                  '[Description
                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                  "cnv"
                                                                                                                                                                  ConvId
                                                                                                                                                                :> ("protocol"
                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                             'PUT
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "remove-member-unqualified"
        (Summary "Remove a member from a conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "leave-conversation"
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (Until 'V2
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("members"
                                                             :> (Capture'
                                                                   '[Description "Target User ID"]
                                                                   "usr"
                                                                   UserId
                                                                 :> RemoveFromConversationVerb)))))))))))))))
      :<|> (Named
              "remove-member"
              (Summary "Remove a member from a conversation"
               :> (MakesFederatedCall 'Galley "leave-conversation"
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> ("conversations"
                                                       :> (QualifiedCapture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("members"
                                                               :> (QualifiedCapture'
                                                                     '[Description "Target User ID"]
                                                                     "usr"
                                                                     UserId
                                                                   :> RemoveFromConversationVerb))))))))))))))
            :<|> (Named
                    "update-other-member-unqualified"
                    (Summary "Update membership of the specified user (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'ConvMemberNotFound
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyOtherConversationMember)
                                                             :> (CanThrow 'InvalidTarget
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("members"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Target User ID"]
                                                                                       "usr"
                                                                                       UserId
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           OtherMemberUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "Membership updated"]
                                                                                              ()))))))))))))))))))
                  :<|> (Named
                          "update-other-member"
                          (Summary "Update membership of the specified user"
                           :> (Description "**Note**: at least one field has to be provided."
                               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'ConvMemberNotFound
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyOtherConversationMember)
                                                               :> (CanThrow 'InvalidTarget
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("members"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Target User ID"]
                                                                                         "usr"
                                                                                         UserId
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             OtherMemberUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                '[RespondEmpty
                                                                                                    200
                                                                                                    "Membership updated"]
                                                                                                ())))))))))))))))))
                        :<|> (Named
                                "update-conversation-name-deprecated"
                                (Summary "Update conversation name (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/name` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (CanThrow
                                                           ('ActionDenied 'ModifyConversationName)
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationRename
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Name unchanged"
                                                                                             "Name updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event)))))))))))))))
                              :<|> (Named
                                      "update-conversation-name-unqualified"
                                      (Summary "Update conversation name (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/name` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationName)
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("name"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 ConversationRename
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Name unchanged"
                                                                                                       "Name updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-name"
                                            (Summary "Update conversation name"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationName)
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (QualifiedCapture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("name"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ConversationRename
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  (UpdateResponses
                                                                                                     "Name updated"
                                                                                                     "Name unchanged"
                                                                                                     Event)
                                                                                                  (UpdateResult
                                                                                                     Event))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-message-timer-unqualified"
                                                  (Summary
                                                     "Update the message timer for a conversation (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Brig "get-users-by-ids"
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'ModifyConversationMessageTimer)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("message-timer"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 ConversationMessageTimerUpdate
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    (UpdateResponses
                                                                                                                       "Message timer unchanged"
                                                                                                                       "Message timer updated"
                                                                                                                       Event)
                                                                                                                    (UpdateResult
                                                                                                                       Event)))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-message-timer"
                                                        (Summary
                                                           "Update the message timer for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationMessageTimer)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("message-timer"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationMessageTimerUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Message timer unchanged"
                                                                                                                     "Message timer updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event)))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-receipt-mode-unqualified"
                                                              (Summary
                                                                 "Update receipt mode for a conversation (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "on-conversation-updated"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-mls-message-sent"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "update-conversation"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'ModifyConversationReceiptMode)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> ("conversations"
                                                                                                                   :> (Capture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("receipt-mode"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationReceiptModeUpdate
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Receipt mode unchanged"
                                                                                                                                       "Receipt mode updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-receipt-mode"
                                                                    (Summary
                                                                       "Update receipt mode for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Galley
                                                                                   "update-conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Brig
                                                                                       "get-users-by-ids"
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationReceiptMode)
                                                                                                 :> (CanThrow
                                                                                                       'ConvAccessDenied
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (CanThrow
                                                                                                               'InvalidOperation
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("receipt-mode"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               ConversationReceiptModeUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Receipt mode unchanged"
                                                                                                                                     "Receipt mode updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access-unqualified"
                                                                          (Summary
                                                                             "Update access modes for a conversation (deprecated)"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (Until 'V3
                                                                                           :> (Description
                                                                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'ModifyConversationAccess)
                                                                                                           :> (CanThrow
                                                                                                                 ('ActionDenied
                                                                                                                    'RemoveConversationMember)
                                                                                                               :> (CanThrow
                                                                                                                     'ConvAccessDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'ConvNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidOperation
                                                                                                                           :> (CanThrow
                                                                                                                                 'InvalidTargetAccess
                                                                                                                               :> ("conversations"
                                                                                                                                   :> (Capture'
                                                                                                                                         '[Description
                                                                                                                                             "Conversation ID"]
                                                                                                                                         "cnv"
                                                                                                                                         ConvId
                                                                                                                                       :> ("access"
                                                                                                                                           :> (VersionedReqBody
                                                                                                                                                 'V2
                                                                                                                                                 '[JSON]
                                                                                                                                                 ConversationAccessData
                                                                                                                                               :> MultiVerb
                                                                                                                                                    'PUT
                                                                                                                                                    '[JSON]
                                                                                                                                                    (UpdateResponses
                                                                                                                                                       "Access unchanged"
                                                                                                                                                       "Access updated"
                                                                                                                                                       Event)
                                                                                                                                                    (UpdateResult
                                                                                                                                                       Event)))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access@v2"
                                                                                (Summary
                                                                                   "Update access modes for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (Until
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationAccess)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidTargetAccess
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("access"
                                                                                                                                             :> (VersionedReqBody
                                                                                                                                                   'V2
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationAccessData
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Access unchanged"
                                                                                                                                                         "Access updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-access"
                                                                                      (Summary
                                                                                         "Update access modes for a conversation"
                                                                                       :> (MakesFederatedCall
                                                                                             'Galley
                                                                                             "on-conversation-updated"
                                                                                           :> (MakesFederatedCall
                                                                                                 'Galley
                                                                                                 "on-mls-message-sent"
                                                                                               :> (MakesFederatedCall
                                                                                                     'Brig
                                                                                                     "get-users-by-ids"
                                                                                                   :> (From
                                                                                                         'V3
                                                                                                       :> (ZLocalUser
                                                                                                           :> (ZConn
                                                                                                               :> (CanThrow
                                                                                                                     ('ActionDenied
                                                                                                                        'ModifyConversationAccess)
                                                                                                                   :> (CanThrow
                                                                                                                         ('ActionDenied
                                                                                                                            'RemoveConversationMember)
                                                                                                                       :> (CanThrow
                                                                                                                             'ConvAccessDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'ConvNotFound
                                                                                                                               :> (CanThrow
                                                                                                                                     'InvalidOperation
                                                                                                                                   :> (CanThrow
                                                                                                                                         'InvalidTargetAccess
                                                                                                                                       :> ("conversations"
                                                                                                                                           :> (QualifiedCapture'
                                                                                                                                                 '[Description
                                                                                                                                                     "Conversation ID"]
                                                                                                                                                 "cnv"
                                                                                                                                                 ConvId
                                                                                                                                               :> ("access"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         ConversationAccessData
                                                                                                                                                       :> MultiVerb
                                                                                                                                                            'PUT
                                                                                                                                                            '[JSON]
                                                                                                                                                            (UpdateResponses
                                                                                                                                                               "Access unchanged"
                                                                                                                                                               "Access updated"
                                                                                                                                                               Event)
                                                                                                                                                            (UpdateResult
                                                                                                                                                               Event))))))))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-conversation-self-unqualified"
                                                                                            (Summary
                                                                                               "Get self membership properties (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("self"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (Maybe
                                                                                                                         Member)))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-self-unqualified"
                                                                                                  (Summary
                                                                                                     "Update self membership properties (deprecated)"
                                                                                                   :> (Deprecated
                                                                                                       :> (Description
                                                                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                                                                           :> (CanThrow
                                                                                                                 'ConvNotFound
                                                                                                               :> (ZLocalUser
                                                                                                                   :> (ZConn
                                                                                                                       :> ("conversations"
                                                                                                                           :> (Capture'
                                                                                                                                 '[Description
                                                                                                                                     "Conversation ID"]
                                                                                                                                 "cnv"
                                                                                                                                 ConvId
                                                                                                                               :> ("self"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         MemberUpdate
                                                                                                                                       :> MultiVerb
                                                                                                                                            'PUT
                                                                                                                                            '[JSON]
                                                                                                                                            '[RespondEmpty
                                                                                                                                                200
                                                                                                                                                "Update successful"]
                                                                                                                                            ()))))))))))
                                                                                                :<|> (Named
                                                                                                        "update-conversation-self"
                                                                                                        (Summary
                                                                                                           "Update self membership properties"
                                                                                                         :> (Description
                                                                                                               "**Note**: at least one field has to be provided."
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (ZLocalUser
                                                                                                                     :> (ZConn
                                                                                                                         :> ("conversations"
                                                                                                                             :> (QualifiedCapture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("self"
                                                                                                                                     :> (ReqBody
                                                                                                                                           '[JSON]
                                                                                                                                           MemberUpdate
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              '[RespondEmpty
                                                                                                                                                  200
                                                                                                                                                  "Update successful"]
                                                                                                                                              ())))))))))
                                                                                                      :<|> Named
                                                                                                             "update-conversation-protocol"
                                                                                                             (Summary
                                                                                                                "Update the protocol of the conversation"
                                                                                                              :> (From
                                                                                                                    'V5
                                                                                                                  :> (Description
                                                                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                      :> (CanThrow
                                                                                                                            'ConvNotFound
                                                                                                                          :> (CanThrow
                                                                                                                                'ConvInvalidProtocolTransition
                                                                                                                              :> (CanThrow
                                                                                                                                    ('ActionDenied
                                                                                                                                       'LeaveConversation)
                                                                                                                                  :> (CanThrow
                                                                                                                                        'InvalidOperation
                                                                                                                                      :> (CanThrow
                                                                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'NotATeamMember
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'TeamNotFound
                                                                                                                                                      :> (ZLocalUser
                                                                                                                                                          :> (ZConn
                                                                                                                                                              :> ("conversations"
                                                                                                                                                                  :> (QualifiedCapture'
                                                                                                                                                                        '[Description
                                                                                                                                                                            "Conversation ID"]
                                                                                                                                                                        "cnv"
                                                                                                                                                                        ConvId
                                                                                                                                                                      :> ("protocol"
                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                '[JSON]
                                                                                                                                                                                ProtocolUpdate
                                                                                                                                                                              :> MultiVerb
                                                                                                                                                                                   'PUT
                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                   ConvUpdateResponses
                                                                                                                                                                                   (UpdateResult
                                                                                                                                                                                      Event)))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"remove-member" (((HasAnnotation 'Remote "galley" "leave-conversation",
  (HasAnnotation 'Remote "galley" "on-conversation-updated",
   (HasAnnotation 'Remote "galley" "on-mls-message-sent",
    (HasAnnotation 'Remote "brig" "get-users-by-ids",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> Qualified UserId
 -> Sem
      '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (Maybe Event))
-> Dict (HasAnnotation 'Remote "galley" "leave-conversation")
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> Qualified UserId
 -> Sem
      '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (Maybe Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> Sem
     '[Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'RemoveConversationMember) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input Env) r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member ProposalStore r, Member Random r,
 Member SubConversationStore r, Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> Sem r (Maybe Event)
removeMemberQualified))
    API
  (Named
     "remove-member"
     (Summary "Remove a member from a conversation"
      :> (MakesFederatedCall 'Galley "leave-conversation"
          :> (MakesFederatedCall 'Galley "on-conversation-updated"
              :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                  :> (MakesFederatedCall 'Brig "get-users-by-ids"
                      :> (ZLocalUser
                          :> (ZConn
                              :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                  :> (CanThrow 'ConvNotFound
                                      :> (CanThrow 'InvalidOperation
                                          :> ("conversations"
                                              :> (QualifiedCapture'
                                                    '[Description "Conversation ID"] "cnv" ConvId
                                                  :> ("members"
                                                      :> (QualifiedCapture'
                                                            '[Description "Target User ID"]
                                                            "usr"
                                                            UserId
                                                          :> RemoveFromConversationVerb)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-other-member-unqualified"
        (Summary "Update membership of the specified user (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'ConvMemberNotFound
                                             :> (CanThrow
                                                   ('ActionDenied 'ModifyOtherConversationMember)
                                                 :> (CanThrow 'InvalidTarget
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("members"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Target User ID"]
                                                                           "usr"
                                                                           UserId
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               OtherMemberUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200
                                                                                      "Membership updated"]
                                                                                  ()))))))))))))))))))
      :<|> (Named
              "update-other-member"
              (Summary "Update membership of the specified user"
               :> (Description "**Note**: at least one field has to be provided."
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvMemberNotFound
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyOtherConversationMember)
                                                   :> (CanThrow 'InvalidTarget
                                                       :> (CanThrow 'InvalidOperation
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("members"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Target User ID"]
                                                                             "usr"
                                                                             UserId
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 OtherMemberUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200
                                                                                        "Membership updated"]
                                                                                    ())))))))))))))))))
            :<|> (Named
                    "update-conversation-name-deprecated"
                    (Summary "Update conversation name (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/name` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationRename
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Name unchanged"
                                                                                 "Name updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event)))))))))))))))
                  :<|> (Named
                          "update-conversation-name-unqualified"
                          (Summary "Update conversation name (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/name` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("name"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     ConversationRename
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Name unchanged"
                                                                                           "Name updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event))))))))))))))))
                        :<|> (Named
                                "update-conversation-name"
                                (Summary "Update conversation name"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("name"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ConversationRename
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      (UpdateResponses
                                                                                         "Name updated"
                                                                                         "Name unchanged"
                                                                                         Event)
                                                                                      (UpdateResult
                                                                                         Event))))))))))))))
                              :<|> (Named
                                      "update-conversation-message-timer-unqualified"
                                      (Summary
                                         "Update the message timer for a conversation (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'ModifyConversationMessageTimer)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("message-timer"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ConversationMessageTimerUpdate
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        (UpdateResponses
                                                                                                           "Message timer unchanged"
                                                                                                           "Message timer updated"
                                                                                                           Event)
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-message-timer"
                                            (Summary "Update the message timer for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationMessageTimer)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("message-timer"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationMessageTimerUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Message timer unchanged"
                                                                                                         "Message timer updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event)))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-receipt-mode-unqualified"
                                                  (Summary
                                                     "Update receipt mode for a conversation (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "update-conversation"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationReceiptMode)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("receipt-mode"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Receipt mode unchanged"
                                                                                                                           "Receipt mode updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-receipt-mode"
                                                        (Summary
                                                           "Update receipt mode for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "update-conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationReceiptMode)
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("receipt-mode"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Receipt mode unchanged"
                                                                                                                         "Receipt mode updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access-unqualified"
                                                              (Summary
                                                                 "Update access modes for a conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (Until 'V3
                                                                               :> (Description
                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'ModifyConversationAccess)
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'RemoveConversationMember)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidTargetAccess
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("access"
                                                                                                                               :> (VersionedReqBody
                                                                                                                                     'V2
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationAccessData
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Access unchanged"
                                                                                                                                           "Access updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event)))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access@v2"
                                                                    (Summary
                                                                       "Update access modes for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (Until 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationAccess)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidTargetAccess
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("access"
                                                                                                                                 :> (VersionedReqBody
                                                                                                                                       'V2
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationAccessData
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Access unchanged"
                                                                                                                                             "Access updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access"
                                                                          (Summary
                                                                             "Update access modes for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (From 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationAccess)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidTargetAccess
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("access"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationAccessData
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Access unchanged"
                                                                                                                                                   "Access updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "get-conversation-self-unqualified"
                                                                                (Summary
                                                                                   "Get self membership properties (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("self"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (Maybe
                                                                                                             Member)))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-self-unqualified"
                                                                                      (Summary
                                                                                         "Update self membership properties (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("self"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             MemberUpdate
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "Update successful"]
                                                                                                                                ()))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-self"
                                                                                            (Summary
                                                                                               "Update self membership properties"
                                                                                             :> (Description
                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("self"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               MemberUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  '[RespondEmpty
                                                                                                                                      200
                                                                                                                                      "Update successful"]
                                                                                                                                  ())))))))))
                                                                                          :<|> Named
                                                                                                 "update-conversation-protocol"
                                                                                                 (Summary
                                                                                                    "Update the protocol of the conversation"
                                                                                                  :> (From
                                                                                                        'V5
                                                                                                      :> (Description
                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                          :> (CanThrow
                                                                                                                'ConvNotFound
                                                                                                              :> (CanThrow
                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                  :> (CanThrow
                                                                                                                        ('ActionDenied
                                                                                                                           'LeaveConversation)
                                                                                                                      :> (CanThrow
                                                                                                                            'InvalidOperation
                                                                                                                          :> (CanThrow
                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (ZLocalUser
                                                                                                                                              :> (ZConn
                                                                                                                                                  :> ("conversations"
                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                            '[Description
                                                                                                                                                                "Conversation ID"]
                                                                                                                                                            "cnv"
                                                                                                                                                            ConvId
                                                                                                                                                          :> ("protocol"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                       'PUT
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                       (UpdateResult
                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "remove-member"
        (Summary "Remove a member from a conversation"
         :> (MakesFederatedCall 'Galley "leave-conversation"
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> ("conversations"
                                                 :> (QualifiedCapture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("members"
                                                         :> (QualifiedCapture'
                                                               '[Description "Target User ID"]
                                                               "usr"
                                                               UserId
                                                             :> RemoveFromConversationVerb))))))))))))))
      :<|> (Named
              "update-other-member-unqualified"
              (Summary "Update membership of the specified user (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'ConvMemberNotFound
                                                   :> (CanThrow
                                                         ('ActionDenied
                                                            'ModifyOtherConversationMember)
                                                       :> (CanThrow 'InvalidTarget
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("members"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Target User ID"]
                                                                                 "usr"
                                                                                 UserId
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     OtherMemberUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "Membership updated"]
                                                                                        ()))))))))))))))))))
            :<|> (Named
                    "update-other-member"
                    (Summary "Update membership of the specified user"
                     :> (Description "**Note**: at least one field has to be provided."
                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'ConvMemberNotFound
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyOtherConversationMember)
                                                         :> (CanThrow 'InvalidTarget
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("members"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Target User ID"]
                                                                                   "usr"
                                                                                   UserId
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       OtherMemberUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          '[RespondEmpty
                                                                                              200
                                                                                              "Membership updated"]
                                                                                          ())))))))))))))))))
                  :<|> (Named
                          "update-conversation-name-deprecated"
                          (Summary "Update conversation name (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/name` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationRename
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Name unchanged"
                                                                                       "Name updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event)))))))))))))))
                        :<|> (Named
                                "update-conversation-name-unqualified"
                                (Summary "Update conversation name (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/name` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (CanThrow
                                                           ('ActionDenied 'ModifyConversationName)
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("name"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           ConversationRename
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Name unchanged"
                                                                                                 "Name updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))
                              :<|> (Named
                                      "update-conversation-name"
                                      (Summary "Update conversation name"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationName)
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (QualifiedCapture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("name"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ConversationRename
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            (UpdateResponses
                                                                                               "Name updated"
                                                                                               "Name unchanged"
                                                                                               Event)
                                                                                            (UpdateResult
                                                                                               Event))))))))))))))
                                    :<|> (Named
                                            "update-conversation-message-timer-unqualified"
                                            (Summary
                                               "Update the message timer for a conversation (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:cnv/message-timer` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Brig "get-users-by-ids"
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'ModifyConversationMessageTimer)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("message-timer"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           ConversationMessageTimerUpdate
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              (UpdateResponses
                                                                                                                 "Message timer unchanged"
                                                                                                                 "Message timer updated"
                                                                                                                 Event)
                                                                                                              (UpdateResult
                                                                                                                 Event)))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-message-timer"
                                                  (Summary
                                                     "Update the message timer for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationMessageTimer)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("message-timer"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationMessageTimerUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Message timer unchanged"
                                                                                                               "Message timer updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event)))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-receipt-mode-unqualified"
                                                        (Summary
                                                           "Update receipt mode for a conversation (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                                 :> (MakesFederatedCall
                                                                       'Galley
                                                                       "on-conversation-updated"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-mls-message-sent"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "update-conversation"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'ModifyConversationReceiptMode)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> ("conversations"
                                                                                                             :> (Capture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("receipt-mode"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationReceiptModeUpdate
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Receipt mode unchanged"
                                                                                                                                 "Receipt mode updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-receipt-mode"
                                                              (Summary
                                                                 "Update receipt mode for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Galley
                                                                             "update-conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Brig
                                                                                 "get-users-by-ids"
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationReceiptMode)
                                                                                           :> (CanThrow
                                                                                                 'ConvAccessDenied
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (CanThrow
                                                                                                         'InvalidOperation
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("receipt-mode"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         ConversationReceiptModeUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Receipt mode unchanged"
                                                                                                                               "Receipt mode updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access-unqualified"
                                                                    (Summary
                                                                       "Update access modes for a conversation (deprecated)"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (Until 'V3
                                                                                     :> (Description
                                                                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'ModifyConversationAccess)
                                                                                                     :> (CanThrow
                                                                                                           ('ActionDenied
                                                                                                              'RemoveConversationMember)
                                                                                                         :> (CanThrow
                                                                                                               'ConvAccessDenied
                                                                                                             :> (CanThrow
                                                                                                                   'ConvNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidOperation
                                                                                                                     :> (CanThrow
                                                                                                                           'InvalidTargetAccess
                                                                                                                         :> ("conversations"
                                                                                                                             :> (Capture'
                                                                                                                                   '[Description
                                                                                                                                       "Conversation ID"]
                                                                                                                                   "cnv"
                                                                                                                                   ConvId
                                                                                                                                 :> ("access"
                                                                                                                                     :> (VersionedReqBody
                                                                                                                                           'V2
                                                                                                                                           '[JSON]
                                                                                                                                           ConversationAccessData
                                                                                                                                         :> MultiVerb
                                                                                                                                              'PUT
                                                                                                                                              '[JSON]
                                                                                                                                              (UpdateResponses
                                                                                                                                                 "Access unchanged"
                                                                                                                                                 "Access updated"
                                                                                                                                                 Event)
                                                                                                                                              (UpdateResult
                                                                                                                                                 Event)))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access@v2"
                                                                          (Summary
                                                                             "Update access modes for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (Until 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationAccess)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidTargetAccess
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("access"
                                                                                                                                       :> (VersionedReqBody
                                                                                                                                             'V2
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationAccessData
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Access unchanged"
                                                                                                                                                   "Access updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-access"
                                                                                (Summary
                                                                                   "Update access modes for a conversation"
                                                                                 :> (MakesFederatedCall
                                                                                       'Galley
                                                                                       "on-conversation-updated"
                                                                                     :> (MakesFederatedCall
                                                                                           'Galley
                                                                                           "on-mls-message-sent"
                                                                                         :> (MakesFederatedCall
                                                                                               'Brig
                                                                                               "get-users-by-ids"
                                                                                             :> (From
                                                                                                   'V3
                                                                                                 :> (ZLocalUser
                                                                                                     :> (ZConn
                                                                                                         :> (CanThrow
                                                                                                               ('ActionDenied
                                                                                                                  'ModifyConversationAccess)
                                                                                                             :> (CanThrow
                                                                                                                   ('ActionDenied
                                                                                                                      'RemoveConversationMember)
                                                                                                                 :> (CanThrow
                                                                                                                       'ConvAccessDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'ConvNotFound
                                                                                                                         :> (CanThrow
                                                                                                                               'InvalidOperation
                                                                                                                             :> (CanThrow
                                                                                                                                   'InvalidTargetAccess
                                                                                                                                 :> ("conversations"
                                                                                                                                     :> (QualifiedCapture'
                                                                                                                                           '[Description
                                                                                                                                               "Conversation ID"]
                                                                                                                                           "cnv"
                                                                                                                                           ConvId
                                                                                                                                         :> ("access"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   ConversationAccessData
                                                                                                                                                 :> MultiVerb
                                                                                                                                                      'PUT
                                                                                                                                                      '[JSON]
                                                                                                                                                      (UpdateResponses
                                                                                                                                                         "Access unchanged"
                                                                                                                                                         "Access updated"
                                                                                                                                                         Event)
                                                                                                                                                      (UpdateResult
                                                                                                                                                         Event))))))))))))))))))
                                                                              :<|> (Named
                                                                                      "get-conversation-self-unqualified"
                                                                                      (Summary
                                                                                         "Get self membership properties (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (ZLocalUser
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("self"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (Maybe
                                                                                                                   Member)))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-self-unqualified"
                                                                                            (Summary
                                                                                               "Update self membership properties (deprecated)"
                                                                                             :> (Deprecated
                                                                                                 :> (Description
                                                                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                                                                     :> (CanThrow
                                                                                                           'ConvNotFound
                                                                                                         :> (ZLocalUser
                                                                                                             :> (ZConn
                                                                                                                 :> ("conversations"
                                                                                                                     :> (Capture'
                                                                                                                           '[Description
                                                                                                                               "Conversation ID"]
                                                                                                                           "cnv"
                                                                                                                           ConvId
                                                                                                                         :> ("self"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   MemberUpdate
                                                                                                                                 :> MultiVerb
                                                                                                                                      'PUT
                                                                                                                                      '[JSON]
                                                                                                                                      '[RespondEmpty
                                                                                                                                          200
                                                                                                                                          "Update successful"]
                                                                                                                                      ()))))))))))
                                                                                          :<|> (Named
                                                                                                  "update-conversation-self"
                                                                                                  (Summary
                                                                                                     "Update self membership properties"
                                                                                                   :> (Description
                                                                                                         "**Note**: at least one field has to be provided."
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (ZLocalUser
                                                                                                               :> (ZConn
                                                                                                                   :> ("conversations"
                                                                                                                       :> (QualifiedCapture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("self"
                                                                                                                               :> (ReqBody
                                                                                                                                     '[JSON]
                                                                                                                                     MemberUpdate
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        '[RespondEmpty
                                                                                                                                            200
                                                                                                                                            "Update successful"]
                                                                                                                                        ())))))))))
                                                                                                :<|> Named
                                                                                                       "update-conversation-protocol"
                                                                                                       (Summary
                                                                                                          "Update the protocol of the conversation"
                                                                                                        :> (From
                                                                                                              'V5
                                                                                                            :> (Description
                                                                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                                :> (CanThrow
                                                                                                                      'ConvNotFound
                                                                                                                    :> (CanThrow
                                                                                                                          'ConvInvalidProtocolTransition
                                                                                                                        :> (CanThrow
                                                                                                                              ('ActionDenied
                                                                                                                                 'LeaveConversation)
                                                                                                                            :> (CanThrow
                                                                                                                                  'InvalidOperation
                                                                                                                                :> (CanThrow
                                                                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'NotATeamMember
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'TeamNotFound
                                                                                                                                                :> (ZLocalUser
                                                                                                                                                    :> (ZConn
                                                                                                                                                        :> ("conversations"
                                                                                                                                                            :> (QualifiedCapture'
                                                                                                                                                                  '[Description
                                                                                                                                                                      "Conversation ID"]
                                                                                                                                                                  "cnv"
                                                                                                                                                                  ConvId
                                                                                                                                                                :> ("protocol"
                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          ProtocolUpdate
                                                                                                                                                                        :> MultiVerb
                                                                                                                                                                             'PUT
                                                                                                                                                                             '[JSON]
                                                                                                                                                                             ConvUpdateResponses
                                                                                                                                                                             (UpdateResult
                                                                                                                                                                                Event))))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-other-member-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> UserId
 -> OtherMemberUpdate
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvMemberNotFound ()),
        Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
        Error (Tagged 'InvalidTarget ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> UserId
 -> OtherMemberUpdate
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvMemberNotFound ()),
        Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
        Error (Tagged 'InvalidTarget ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()))
   r,
 Member (Error (Tagged 'InvalidTarget ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvMemberNotFound ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> UserId -> OtherMemberUpdate -> Sem r ()
updateOtherMemberUnqualified))
    API
  (Named
     "update-other-member-unqualified"
     (Summary "Update membership of the specified user (deprecated)"
      :> (Deprecated
          :> (Description
                "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                      :> (MakesFederatedCall 'Brig "get-users-by-ids"
                          :> (ZLocalUser
                              :> (ZConn
                                  :> (CanThrow 'ConvNotFound
                                      :> (CanThrow 'ConvMemberNotFound
                                          :> (CanThrow
                                                ('ActionDenied 'ModifyOtherConversationMember)
                                              :> (CanThrow 'InvalidTarget
                                                  :> (CanThrow 'InvalidOperation
                                                      :> ("conversations"
                                                          :> (Capture'
                                                                '[Description "Conversation ID"]
                                                                "cnv"
                                                                ConvId
                                                              :> ("members"
                                                                  :> (Capture'
                                                                        '[Description
                                                                            "Target User ID"]
                                                                        "usr"
                                                                        UserId
                                                                      :> (ReqBody
                                                                            '[JSON]
                                                                            OtherMemberUpdate
                                                                          :> MultiVerb
                                                                               'PUT
                                                                               '[JSON]
                                                                               '[RespondEmpty
                                                                                   200
                                                                                   "Membership updated"]
                                                                               ())))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-other-member"
        (Summary "Update membership of the specified user"
         :> (Description "**Note**: at least one field has to be provided."
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvMemberNotFound
                                         :> (CanThrow ('ActionDenied 'ModifyOtherConversationMember)
                                             :> (CanThrow 'InvalidTarget
                                                 :> (CanThrow 'InvalidOperation
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("members"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Target User ID"]
                                                                       "usr"
                                                                       UserId
                                                                     :> (ReqBody
                                                                           '[JSON] OtherMemberUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200
                                                                                  "Membership updated"]
                                                                              ())))))))))))))))))
      :<|> (Named
              "update-conversation-name-deprecated"
              (Summary "Update conversation name (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/name` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> (ReqBody
                                                                     '[JSON] ConversationRename
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        (UpdateResponses
                                                                           "Name unchanged"
                                                                           "Name updated"
                                                                           Event)
                                                                        (UpdateResult
                                                                           Event)))))))))))))))
            :<|> (Named
                    "update-conversation-name-unqualified"
                    (Summary "Update conversation name (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/name` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("name"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               ConversationRename
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Name unchanged"
                                                                                     "Name updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event))))))))))))))))
                  :<|> (Named
                          "update-conversation-name"
                          (Summary "Update conversation name"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("name"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ConversationRename
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                (UpdateResponses
                                                                                   "Name updated"
                                                                                   "Name unchanged"
                                                                                   Event)
                                                                                (UpdateResult
                                                                                   Event))))))))))))))
                        :<|> (Named
                                "update-conversation-message-timer-unqualified"
                                (Summary "Update the message timer for a conversation (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'ModifyConversationMessageTimer)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("message-timer"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ConversationMessageTimerUpdate
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  (UpdateResponses
                                                                                                     "Message timer unchanged"
                                                                                                     "Message timer updated"
                                                                                                     Event)
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))
                              :<|> (Named
                                      "update-conversation-message-timer"
                                      (Summary "Update the message timer for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationMessageTimer)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("message-timer"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationMessageTimerUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Message timer unchanged"
                                                                                                   "Message timer updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event)))))))))))))))
                                    :<|> (Named
                                            "update-conversation-receipt-mode-unqualified"
                                            (Summary
                                               "Update receipt mode for a conversation (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Galley "update-conversation"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationReceiptMode)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("receipt-mode"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationReceiptModeUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Receipt mode unchanged"
                                                                                                                     "Receipt mode updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-receipt-mode"
                                                  (Summary "Update receipt mode for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Galley "update-conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationReceiptMode)
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("receipt-mode"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             ConversationReceiptModeUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Receipt mode unchanged"
                                                                                                                   "Receipt mode updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access-unqualified"
                                                        (Summary
                                                           "Update access modes for a conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (Until 'V3
                                                                         :> (Description
                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'ModifyConversationAccess)
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'RemoveConversationMember)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> (CanThrow
                                                                                                               'InvalidTargetAccess
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("access"
                                                                                                                         :> (VersionedReqBody
                                                                                                                               'V2
                                                                                                                               '[JSON]
                                                                                                                               ConversationAccessData
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Access unchanged"
                                                                                                                                     "Access updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event)))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access@v2"
                                                              (Summary
                                                                 "Update access modes for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (Until 'V3
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationAccess)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidTargetAccess
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("access"
                                                                                                                           :> (VersionedReqBody
                                                                                                                                 'V2
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationAccessData
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Access unchanged"
                                                                                                                                       "Access updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access"
                                                                    (Summary
                                                                       "Update access modes for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (From 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationAccess)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidTargetAccess
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("access"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationAccessData
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Access unchanged"
                                                                                                                                             "Access updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "get-conversation-self-unqualified"
                                                                          (Summary
                                                                             "Get self membership properties (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("self"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (Maybe
                                                                                                       Member)))))))
                                                                        :<|> (Named
                                                                                "update-conversation-self-unqualified"
                                                                                (Summary
                                                                                   "Update self membership properties (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("self"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       MemberUpdate
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "Update successful"]
                                                                                                                          ()))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-self"
                                                                                      (Summary
                                                                                         "Update self membership properties"
                                                                                       :> (Description
                                                                                             "**Note**: at least one field has to be provided."
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("self"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         MemberUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                200
                                                                                                                                "Update successful"]
                                                                                                                            ())))))))))
                                                                                    :<|> Named
                                                                                           "update-conversation-protocol"
                                                                                           (Summary
                                                                                              "Update the protocol of the conversation"
                                                                                            :> (From
                                                                                                  'V5
                                                                                                :> (Description
                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                    :> (CanThrow
                                                                                                          'ConvNotFound
                                                                                                        :> (CanThrow
                                                                                                              'ConvInvalidProtocolTransition
                                                                                                            :> (CanThrow
                                                                                                                  ('ActionDenied
                                                                                                                     'LeaveConversation)
                                                                                                                :> (CanThrow
                                                                                                                      'InvalidOperation
                                                                                                                    :> (CanThrow
                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (ZLocalUser
                                                                                                                                        :> (ZConn
                                                                                                                                            :> ("conversations"
                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                      '[Description
                                                                                                                                                          "Conversation ID"]
                                                                                                                                                      "cnv"
                                                                                                                                                      ConvId
                                                                                                                                                    :> ("protocol"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              ProtocolUpdate
                                                                                                                                                            :> MultiVerb
                                                                                                                                                                 'PUT
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                 (UpdateResult
                                                                                                                                                                    Event))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-other-member-unqualified"
        (Summary "Update membership of the specified user (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `PUT /conversations/:cnv_domain/:cnv/members/:usr_domain/:usr` instead"
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'ConvMemberNotFound
                                             :> (CanThrow
                                                   ('ActionDenied 'ModifyOtherConversationMember)
                                                 :> (CanThrow 'InvalidTarget
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("members"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Target User ID"]
                                                                           "usr"
                                                                           UserId
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               OtherMemberUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200
                                                                                      "Membership updated"]
                                                                                  ()))))))))))))))))))
      :<|> (Named
              "update-other-member"
              (Summary "Update membership of the specified user"
               :> (Description "**Note**: at least one field has to be provided."
                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'ConvMemberNotFound
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyOtherConversationMember)
                                                   :> (CanThrow 'InvalidTarget
                                                       :> (CanThrow 'InvalidOperation
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("members"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Target User ID"]
                                                                             "usr"
                                                                             UserId
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 OtherMemberUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    '[RespondEmpty
                                                                                        200
                                                                                        "Membership updated"]
                                                                                    ())))))))))))))))))
            :<|> (Named
                    "update-conversation-name-deprecated"
                    (Summary "Update conversation name (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/name` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationRename
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Name unchanged"
                                                                                 "Name updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event)))))))))))))))
                  :<|> (Named
                          "update-conversation-name-unqualified"
                          (Summary "Update conversation name (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/name` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("name"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     ConversationRename
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Name unchanged"
                                                                                           "Name updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event))))))))))))))))
                        :<|> (Named
                                "update-conversation-name"
                                (Summary "Update conversation name"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (QualifiedCapture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("name"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ConversationRename
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      (UpdateResponses
                                                                                         "Name updated"
                                                                                         "Name unchanged"
                                                                                         Event)
                                                                                      (UpdateResult
                                                                                         Event))))))))))))))
                              :<|> (Named
                                      "update-conversation-message-timer-unqualified"
                                      (Summary
                                         "Update the message timer for a conversation (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:cnv/message-timer` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Brig "get-users-by-ids"
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'ModifyConversationMessageTimer)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("message-timer"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     ConversationMessageTimerUpdate
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        (UpdateResponses
                                                                                                           "Message timer unchanged"
                                                                                                           "Message timer updated"
                                                                                                           Event)
                                                                                                        (UpdateResult
                                                                                                           Event)))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-message-timer"
                                            (Summary "Update the message timer for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationMessageTimer)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("message-timer"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationMessageTimerUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Message timer unchanged"
                                                                                                         "Message timer updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event)))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-receipt-mode-unqualified"
                                                  (Summary
                                                     "Update receipt mode for a conversation (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                           :> (MakesFederatedCall
                                                                 'Galley "on-conversation-updated"
                                                               :> (MakesFederatedCall
                                                                     'Galley "on-mls-message-sent"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "update-conversation"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'ModifyConversationReceiptMode)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> ("conversations"
                                                                                                       :> (Capture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("receipt-mode"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationReceiptModeUpdate
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Receipt mode unchanged"
                                                                                                                           "Receipt mode updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-receipt-mode"
                                                        (Summary
                                                           "Update receipt mode for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Galley "update-conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Brig "get-users-by-ids"
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationReceiptMode)
                                                                                     :> (CanThrow
                                                                                           'ConvAccessDenied
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (CanThrow
                                                                                                   'InvalidOperation
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("receipt-mode"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   ConversationReceiptModeUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Receipt mode unchanged"
                                                                                                                         "Receipt mode updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access-unqualified"
                                                              (Summary
                                                                 "Update access modes for a conversation (deprecated)"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (Until 'V3
                                                                               :> (Description
                                                                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'ModifyConversationAccess)
                                                                                               :> (CanThrow
                                                                                                     ('ActionDenied
                                                                                                        'RemoveConversationMember)
                                                                                                   :> (CanThrow
                                                                                                         'ConvAccessDenied
                                                                                                       :> (CanThrow
                                                                                                             'ConvNotFound
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidOperation
                                                                                                               :> (CanThrow
                                                                                                                     'InvalidTargetAccess
                                                                                                                   :> ("conversations"
                                                                                                                       :> (Capture'
                                                                                                                             '[Description
                                                                                                                                 "Conversation ID"]
                                                                                                                             "cnv"
                                                                                                                             ConvId
                                                                                                                           :> ("access"
                                                                                                                               :> (VersionedReqBody
                                                                                                                                     'V2
                                                                                                                                     '[JSON]
                                                                                                                                     ConversationAccessData
                                                                                                                                   :> MultiVerb
                                                                                                                                        'PUT
                                                                                                                                        '[JSON]
                                                                                                                                        (UpdateResponses
                                                                                                                                           "Access unchanged"
                                                                                                                                           "Access updated"
                                                                                                                                           Event)
                                                                                                                                        (UpdateResult
                                                                                                                                           Event)))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access@v2"
                                                                    (Summary
                                                                       "Update access modes for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (Until 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationAccess)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidTargetAccess
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("access"
                                                                                                                                 :> (VersionedReqBody
                                                                                                                                       'V2
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationAccessData
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Access unchanged"
                                                                                                                                             "Access updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-access"
                                                                          (Summary
                                                                             "Update access modes for a conversation"
                                                                           :> (MakesFederatedCall
                                                                                 'Galley
                                                                                 "on-conversation-updated"
                                                                               :> (MakesFederatedCall
                                                                                     'Galley
                                                                                     "on-mls-message-sent"
                                                                                   :> (MakesFederatedCall
                                                                                         'Brig
                                                                                         "get-users-by-ids"
                                                                                       :> (From 'V3
                                                                                           :> (ZLocalUser
                                                                                               :> (ZConn
                                                                                                   :> (CanThrow
                                                                                                         ('ActionDenied
                                                                                                            'ModifyConversationAccess)
                                                                                                       :> (CanThrow
                                                                                                             ('ActionDenied
                                                                                                                'RemoveConversationMember)
                                                                                                           :> (CanThrow
                                                                                                                 'ConvAccessDenied
                                                                                                               :> (CanThrow
                                                                                                                     'ConvNotFound
                                                                                                                   :> (CanThrow
                                                                                                                         'InvalidOperation
                                                                                                                       :> (CanThrow
                                                                                                                             'InvalidTargetAccess
                                                                                                                           :> ("conversations"
                                                                                                                               :> (QualifiedCapture'
                                                                                                                                     '[Description
                                                                                                                                         "Conversation ID"]
                                                                                                                                     "cnv"
                                                                                                                                     ConvId
                                                                                                                                   :> ("access"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             ConversationAccessData
                                                                                                                                           :> MultiVerb
                                                                                                                                                'PUT
                                                                                                                                                '[JSON]
                                                                                                                                                (UpdateResponses
                                                                                                                                                   "Access unchanged"
                                                                                                                                                   "Access updated"
                                                                                                                                                   Event)
                                                                                                                                                (UpdateResult
                                                                                                                                                   Event))))))))))))))))))
                                                                        :<|> (Named
                                                                                "get-conversation-self-unqualified"
                                                                                (Summary
                                                                                   "Get self membership properties (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (ZLocalUser
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("self"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (Maybe
                                                                                                             Member)))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-self-unqualified"
                                                                                      (Summary
                                                                                         "Update self membership properties (deprecated)"
                                                                                       :> (Deprecated
                                                                                           :> (Description
                                                                                                 "Use `/conversations/:domain/:conv/self` instead."
                                                                                               :> (CanThrow
                                                                                                     'ConvNotFound
                                                                                                   :> (ZLocalUser
                                                                                                       :> (ZConn
                                                                                                           :> ("conversations"
                                                                                                               :> (Capture'
                                                                                                                     '[Description
                                                                                                                         "Conversation ID"]
                                                                                                                     "cnv"
                                                                                                                     ConvId
                                                                                                                   :> ("self"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             MemberUpdate
                                                                                                                           :> MultiVerb
                                                                                                                                'PUT
                                                                                                                                '[JSON]
                                                                                                                                '[RespondEmpty
                                                                                                                                    200
                                                                                                                                    "Update successful"]
                                                                                                                                ()))))))))))
                                                                                    :<|> (Named
                                                                                            "update-conversation-self"
                                                                                            (Summary
                                                                                               "Update self membership properties"
                                                                                             :> (Description
                                                                                                   "**Note**: at least one field has to be provided."
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (ZLocalUser
                                                                                                         :> (ZConn
                                                                                                             :> ("conversations"
                                                                                                                 :> (QualifiedCapture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("self"
                                                                                                                         :> (ReqBody
                                                                                                                               '[JSON]
                                                                                                                               MemberUpdate
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  '[RespondEmpty
                                                                                                                                      200
                                                                                                                                      "Update successful"]
                                                                                                                                  ())))))))))
                                                                                          :<|> Named
                                                                                                 "update-conversation-protocol"
                                                                                                 (Summary
                                                                                                    "Update the protocol of the conversation"
                                                                                                  :> (From
                                                                                                        'V5
                                                                                                      :> (Description
                                                                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                          :> (CanThrow
                                                                                                                'ConvNotFound
                                                                                                              :> (CanThrow
                                                                                                                    'ConvInvalidProtocolTransition
                                                                                                                  :> (CanThrow
                                                                                                                        ('ActionDenied
                                                                                                                           'LeaveConversation)
                                                                                                                      :> (CanThrow
                                                                                                                            'InvalidOperation
                                                                                                                          :> (CanThrow
                                                                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                                                                              :> (CanThrow
                                                                                                                                    'NotATeamMember
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'TeamNotFound
                                                                                                                                          :> (ZLocalUser
                                                                                                                                              :> (ZConn
                                                                                                                                                  :> ("conversations"
                                                                                                                                                      :> (QualifiedCapture'
                                                                                                                                                            '[Description
                                                                                                                                                                "Conversation ID"]
                                                                                                                                                            "cnv"
                                                                                                                                                            ConvId
                                                                                                                                                          :> ("protocol"
                                                                                                                                                              :> (ReqBody
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    ProtocolUpdate
                                                                                                                                                                  :> MultiVerb
                                                                                                                                                                       'PUT
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       ConvUpdateResponses
                                                                                                                                                                       (UpdateResult
                                                                                                                                                                          Event)))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-other-member" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> Qualified UserId
 -> OtherMemberUpdate
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvMemberNotFound ()),
        Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
        Error (Tagged 'InvalidTarget ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> Qualified UserId
 -> OtherMemberUpdate
 -> Sem
      '[Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'ConvMemberNotFound ()),
        Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
        Error (Tagged 'InvalidTarget ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      ())
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> OtherMemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvMemberNotFound ()),
       Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()),
       Error (Tagged 'InvalidTarget ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyOtherConversationMember) ()))
   r,
 Member (Error (Tagged 'InvalidTarget ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvMemberNotFound ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> Qualified UserId
-> OtherMemberUpdate
-> Sem r ()
updateOtherMember))
    API
  (Named
     "update-other-member"
     (Summary "Update membership of the specified user"
      :> (Description "**Note**: at least one field has to be provided."
          :> (MakesFederatedCall 'Galley "on-conversation-updated"
              :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                  :> (MakesFederatedCall 'Brig "get-users-by-ids"
                      :> (ZLocalUser
                          :> (ZConn
                              :> (CanThrow 'ConvNotFound
                                  :> (CanThrow 'ConvMemberNotFound
                                      :> (CanThrow ('ActionDenied 'ModifyOtherConversationMember)
                                          :> (CanThrow 'InvalidTarget
                                              :> (CanThrow 'InvalidOperation
                                                  :> ("conversations"
                                                      :> (QualifiedCapture'
                                                            '[Description "Conversation ID"]
                                                            "cnv"
                                                            ConvId
                                                          :> ("members"
                                                              :> (QualifiedCapture'
                                                                    '[Description "Target User ID"]
                                                                    "usr"
                                                                    UserId
                                                                  :> (ReqBody
                                                                        '[JSON] OtherMemberUpdate
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           '[RespondEmpty
                                                                               200
                                                                               "Membership updated"]
                                                                           ()))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-name-deprecated"
        (Summary "Update conversation name (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/name` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> (ReqBody '[JSON] ConversationRename
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  (UpdateResponses
                                                                     "Name unchanged"
                                                                     "Name updated"
                                                                     Event)
                                                                  (UpdateResult Event)))))))))))))))
      :<|> (Named
              "update-conversation-name-unqualified"
              (Summary "Update conversation name (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/name` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("name"
                                                                   :> (ReqBody
                                                                         '[JSON] ConversationRename
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Name unchanged"
                                                                               "Name updated"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event))))))))))))))))
            :<|> (Named
                    "update-conversation-name"
                    (Summary "Update conversation name"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("name"
                                                                 :> (ReqBody
                                                                       '[JSON] ConversationRename
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          (UpdateResponses
                                                                             "Name updated"
                                                                             "Name unchanged"
                                                                             Event)
                                                                          (UpdateResult
                                                                             Event))))))))))))))
                  :<|> (Named
                          "update-conversation-message-timer-unqualified"
                          (Summary "Update the message timer for a conversation (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'ModifyConversationMessageTimer)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("message-timer"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ConversationMessageTimerUpdate
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            (UpdateResponses
                                                                                               "Message timer unchanged"
                                                                                               "Message timer updated"
                                                                                               Event)
                                                                                            (UpdateResult
                                                                                               Event)))))))))))))))))
                        :<|> (Named
                                "update-conversation-message-timer"
                                (Summary "Update the message timer for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyConversationMessageTimer)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("message-timer"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationMessageTimerUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Message timer unchanged"
                                                                                             "Message timer updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event)))))))))))))))
                              :<|> (Named
                                      "update-conversation-receipt-mode-unqualified"
                                      (Summary "Update receipt mode for a conversation (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Galley "update-conversation"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationReceiptMode)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("receipt-mode"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationReceiptModeUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Receipt mode unchanged"
                                                                                                               "Receipt mode updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-receipt-mode"
                                            (Summary "Update receipt mode for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall
                                                           'Galley "update-conversation"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationReceiptMode)
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("receipt-mode"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       ConversationReceiptModeUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Receipt mode unchanged"
                                                                                                             "Receipt mode updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access-unqualified"
                                                  (Summary
                                                     "Update access modes for a conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (Until 'V3
                                                                   :> (Description
                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'ModifyConversationAccess)
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'RemoveConversationMember)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> (CanThrow
                                                                                                         'InvalidTargetAccess
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("access"
                                                                                                                   :> (VersionedReqBody
                                                                                                                         'V2
                                                                                                                         '[JSON]
                                                                                                                         ConversationAccessData
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Access unchanged"
                                                                                                                               "Access updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event)))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access@v2"
                                                        (Summary
                                                           "Update access modes for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (Until 'V3
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationAccess)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'InvalidTargetAccess
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("access"
                                                                                                                     :> (VersionedReqBody
                                                                                                                           'V2
                                                                                                                           '[JSON]
                                                                                                                           ConversationAccessData
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Access unchanged"
                                                                                                                                 "Access updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access"
                                                              (Summary
                                                                 "Update access modes for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (From 'V3
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationAccess)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidTargetAccess
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("access"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationAccessData
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Access unchanged"
                                                                                                                                       "Access updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "get-conversation-self-unqualified"
                                                                    (Summary
                                                                       "Get self membership properties (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("self"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (Maybe
                                                                                                 Member)))))))
                                                                  :<|> (Named
                                                                          "update-conversation-self-unqualified"
                                                                          (Summary
                                                                             "Update self membership properties (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("self"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 MemberUpdate
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "Update successful"]
                                                                                                                    ()))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-self"
                                                                                (Summary
                                                                                   "Update self membership properties"
                                                                                 :> (Description
                                                                                       "**Note**: at least one field has to be provided."
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("self"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   MemberUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "Update successful"]
                                                                                                                      ())))))))))
                                                                              :<|> Named
                                                                                     "update-conversation-protocol"
                                                                                     (Summary
                                                                                        "Update the protocol of the conversation"
                                                                                      :> (From 'V5
                                                                                          :> (Description
                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                              :> (CanThrow
                                                                                                    'ConvNotFound
                                                                                                  :> (CanThrow
                                                                                                        'ConvInvalidProtocolTransition
                                                                                                      :> (CanThrow
                                                                                                            ('ActionDenied
                                                                                                               'LeaveConversation)
                                                                                                          :> (CanThrow
                                                                                                                'InvalidOperation
                                                                                                              :> (CanThrow
                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (ZLocalUser
                                                                                                                                  :> (ZConn
                                                                                                                                      :> ("conversations"
                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                '[Description
                                                                                                                                                    "Conversation ID"]
                                                                                                                                                "cnv"
                                                                                                                                                ConvId
                                                                                                                                              :> ("protocol"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        ProtocolUpdate
                                                                                                                                                      :> MultiVerb
                                                                                                                                                           'PUT
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                           (UpdateResult
                                                                                                                                                              Event)))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-other-member"
        (Summary "Update membership of the specified user"
         :> (Description "**Note**: at least one field has to be provided."
             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'ConvMemberNotFound
                                         :> (CanThrow ('ActionDenied 'ModifyOtherConversationMember)
                                             :> (CanThrow 'InvalidTarget
                                                 :> (CanThrow 'InvalidOperation
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("members"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Target User ID"]
                                                                       "usr"
                                                                       UserId
                                                                     :> (ReqBody
                                                                           '[JSON] OtherMemberUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  200
                                                                                  "Membership updated"]
                                                                              ())))))))))))))))))
      :<|> (Named
              "update-conversation-name-deprecated"
              (Summary "Update conversation name (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/name` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> (ReqBody
                                                                     '[JSON] ConversationRename
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        (UpdateResponses
                                                                           "Name unchanged"
                                                                           "Name updated"
                                                                           Event)
                                                                        (UpdateResult
                                                                           Event)))))))))))))))
            :<|> (Named
                    "update-conversation-name-unqualified"
                    (Summary "Update conversation name (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/name` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("name"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               ConversationRename
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Name unchanged"
                                                                                     "Name updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event))))))))))))))))
                  :<|> (Named
                          "update-conversation-name"
                          (Summary "Update conversation name"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (QualifiedCapture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("name"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ConversationRename
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                (UpdateResponses
                                                                                   "Name updated"
                                                                                   "Name unchanged"
                                                                                   Event)
                                                                                (UpdateResult
                                                                                   Event))))))))))))))
                        :<|> (Named
                                "update-conversation-message-timer-unqualified"
                                (Summary "Update the message timer for a conversation (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:cnv/message-timer` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'ModifyConversationMessageTimer)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("message-timer"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               ConversationMessageTimerUpdate
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  (UpdateResponses
                                                                                                     "Message timer unchanged"
                                                                                                     "Message timer updated"
                                                                                                     Event)
                                                                                                  (UpdateResult
                                                                                                     Event)))))))))))))))))
                              :<|> (Named
                                      "update-conversation-message-timer"
                                      (Summary "Update the message timer for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationMessageTimer)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("message-timer"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationMessageTimerUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Message timer unchanged"
                                                                                                   "Message timer updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event)))))))))))))))
                                    :<|> (Named
                                            "update-conversation-receipt-mode-unqualified"
                                            (Summary
                                               "Update receipt mode for a conversation (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                                     :> (MakesFederatedCall
                                                           'Galley "on-conversation-updated"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-mls-message-sent"
                                                             :> (MakesFederatedCall
                                                                   'Galley "update-conversation"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'ModifyConversationReceiptMode)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> ("conversations"
                                                                                                 :> (Capture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("receipt-mode"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationReceiptModeUpdate
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Receipt mode unchanged"
                                                                                                                     "Receipt mode updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-receipt-mode"
                                                  (Summary "Update receipt mode for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Galley "update-conversation"
                                                               :> (MakesFederatedCall
                                                                     'Brig "get-users-by-ids"
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationReceiptMode)
                                                                               :> (CanThrow
                                                                                     'ConvAccessDenied
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (CanThrow
                                                                                             'InvalidOperation
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("receipt-mode"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             ConversationReceiptModeUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Receipt mode unchanged"
                                                                                                                   "Receipt mode updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access-unqualified"
                                                        (Summary
                                                           "Update access modes for a conversation (deprecated)"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (Until 'V3
                                                                         :> (Description
                                                                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'ModifyConversationAccess)
                                                                                         :> (CanThrow
                                                                                               ('ActionDenied
                                                                                                  'RemoveConversationMember)
                                                                                             :> (CanThrow
                                                                                                   'ConvAccessDenied
                                                                                                 :> (CanThrow
                                                                                                       'ConvNotFound
                                                                                                     :> (CanThrow
                                                                                                           'InvalidOperation
                                                                                                         :> (CanThrow
                                                                                                               'InvalidTargetAccess
                                                                                                             :> ("conversations"
                                                                                                                 :> (Capture'
                                                                                                                       '[Description
                                                                                                                           "Conversation ID"]
                                                                                                                       "cnv"
                                                                                                                       ConvId
                                                                                                                     :> ("access"
                                                                                                                         :> (VersionedReqBody
                                                                                                                               'V2
                                                                                                                               '[JSON]
                                                                                                                               ConversationAccessData
                                                                                                                             :> MultiVerb
                                                                                                                                  'PUT
                                                                                                                                  '[JSON]
                                                                                                                                  (UpdateResponses
                                                                                                                                     "Access unchanged"
                                                                                                                                     "Access updated"
                                                                                                                                     Event)
                                                                                                                                  (UpdateResult
                                                                                                                                     Event)))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access@v2"
                                                              (Summary
                                                                 "Update access modes for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (Until 'V3
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationAccess)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidTargetAccess
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("access"
                                                                                                                           :> (VersionedReqBody
                                                                                                                                 'V2
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationAccessData
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Access unchanged"
                                                                                                                                       "Access updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-access"
                                                                    (Summary
                                                                       "Update access modes for a conversation"
                                                                     :> (MakesFederatedCall
                                                                           'Galley
                                                                           "on-conversation-updated"
                                                                         :> (MakesFederatedCall
                                                                               'Galley
                                                                               "on-mls-message-sent"
                                                                             :> (MakesFederatedCall
                                                                                   'Brig
                                                                                   "get-users-by-ids"
                                                                                 :> (From 'V3
                                                                                     :> (ZLocalUser
                                                                                         :> (ZConn
                                                                                             :> (CanThrow
                                                                                                   ('ActionDenied
                                                                                                      'ModifyConversationAccess)
                                                                                                 :> (CanThrow
                                                                                                       ('ActionDenied
                                                                                                          'RemoveConversationMember)
                                                                                                     :> (CanThrow
                                                                                                           'ConvAccessDenied
                                                                                                         :> (CanThrow
                                                                                                               'ConvNotFound
                                                                                                             :> (CanThrow
                                                                                                                   'InvalidOperation
                                                                                                                 :> (CanThrow
                                                                                                                       'InvalidTargetAccess
                                                                                                                     :> ("conversations"
                                                                                                                         :> (QualifiedCapture'
                                                                                                                               '[Description
                                                                                                                                   "Conversation ID"]
                                                                                                                               "cnv"
                                                                                                                               ConvId
                                                                                                                             :> ("access"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       ConversationAccessData
                                                                                                                                     :> MultiVerb
                                                                                                                                          'PUT
                                                                                                                                          '[JSON]
                                                                                                                                          (UpdateResponses
                                                                                                                                             "Access unchanged"
                                                                                                                                             "Access updated"
                                                                                                                                             Event)
                                                                                                                                          (UpdateResult
                                                                                                                                             Event))))))))))))))))))
                                                                  :<|> (Named
                                                                          "get-conversation-self-unqualified"
                                                                          (Summary
                                                                             "Get self membership properties (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (ZLocalUser
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("self"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (Maybe
                                                                                                       Member)))))))
                                                                        :<|> (Named
                                                                                "update-conversation-self-unqualified"
                                                                                (Summary
                                                                                   "Update self membership properties (deprecated)"
                                                                                 :> (Deprecated
                                                                                     :> (Description
                                                                                           "Use `/conversations/:domain/:conv/self` instead."
                                                                                         :> (CanThrow
                                                                                               'ConvNotFound
                                                                                             :> (ZLocalUser
                                                                                                 :> (ZConn
                                                                                                     :> ("conversations"
                                                                                                         :> (Capture'
                                                                                                               '[Description
                                                                                                                   "Conversation ID"]
                                                                                                               "cnv"
                                                                                                               ConvId
                                                                                                             :> ("self"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       MemberUpdate
                                                                                                                     :> MultiVerb
                                                                                                                          'PUT
                                                                                                                          '[JSON]
                                                                                                                          '[RespondEmpty
                                                                                                                              200
                                                                                                                              "Update successful"]
                                                                                                                          ()))))))))))
                                                                              :<|> (Named
                                                                                      "update-conversation-self"
                                                                                      (Summary
                                                                                         "Update self membership properties"
                                                                                       :> (Description
                                                                                             "**Note**: at least one field has to be provided."
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (ZLocalUser
                                                                                                   :> (ZConn
                                                                                                       :> ("conversations"
                                                                                                           :> (QualifiedCapture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("self"
                                                                                                                   :> (ReqBody
                                                                                                                         '[JSON]
                                                                                                                         MemberUpdate
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            '[RespondEmpty
                                                                                                                                200
                                                                                                                                "Update successful"]
                                                                                                                            ())))))))))
                                                                                    :<|> Named
                                                                                           "update-conversation-protocol"
                                                                                           (Summary
                                                                                              "Update the protocol of the conversation"
                                                                                            :> (From
                                                                                                  'V5
                                                                                                :> (Description
                                                                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                                                                    :> (CanThrow
                                                                                                          'ConvNotFound
                                                                                                        :> (CanThrow
                                                                                                              'ConvInvalidProtocolTransition
                                                                                                            :> (CanThrow
                                                                                                                  ('ActionDenied
                                                                                                                     'LeaveConversation)
                                                                                                                :> (CanThrow
                                                                                                                      'InvalidOperation
                                                                                                                    :> (CanThrow
                                                                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                                                                        :> (CanThrow
                                                                                                                              'NotATeamMember
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> (ZLocalUser
                                                                                                                                        :> (ZConn
                                                                                                                                            :> ("conversations"
                                                                                                                                                :> (QualifiedCapture'
                                                                                                                                                      '[Description
                                                                                                                                                          "Conversation ID"]
                                                                                                                                                      "cnv"
                                                                                                                                                      ConvId
                                                                                                                                                    :> ("protocol"
                                                                                                                                                        :> (ReqBody
                                                                                                                                                              '[JSON]
                                                                                                                                                              ProtocolUpdate
                                                                                                                                                            :> MultiVerb
                                                                                                                                                                 'PUT
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 ConvUpdateResponses
                                                                                                                                                                 (UpdateResult
                                                                                                                                                                    Event))))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-name-deprecated" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InvalidInput) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationName) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem r (UpdateResult Event)
updateUnqualifiedConversationName))
    API
  (Named
     "update-conversation-name-deprecated"
     (Summary "Update conversation name (deprecated)"
      :> (Deprecated
          :> (Description "Use `/conversations/:domain/:conv/name` instead."
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                      :> (MakesFederatedCall 'Brig "get-users-by-ids"
                          :> (CanThrow ('ActionDenied 'ModifyConversationName)
                              :> (CanThrow 'ConvNotFound
                                  :> (CanThrow 'InvalidOperation
                                      :> (ZLocalUser
                                          :> (ZConn
                                              :> ("conversations"
                                                  :> (Capture'
                                                        '[Description "Conversation ID"]
                                                        "cnv"
                                                        ConvId
                                                      :> (ReqBody '[JSON] ConversationRename
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               (UpdateResponses
                                                                  "Name unchanged"
                                                                  "Name updated"
                                                                  Event)
                                                               (UpdateResult Event))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-name-unqualified"
        (Summary "Update conversation name (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/name` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("name"
                                                             :> (ReqBody '[JSON] ConversationRename
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Name unchanged"
                                                                         "Name updated"
                                                                         Event)
                                                                      (UpdateResult
                                                                         Event))))))))))))))))
      :<|> (Named
              "update-conversation-name"
              (Summary "Update conversation name"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (CanThrow ('ActionDenied 'ModifyConversationName)
                               :> (CanThrow 'ConvNotFound
                                   :> (CanThrow 'InvalidOperation
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (QualifiedCapture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("name"
                                                           :> (ReqBody '[JSON] ConversationRename
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    (UpdateResponses
                                                                       "Name updated"
                                                                       "Name unchanged"
                                                                       Event)
                                                                    (UpdateResult
                                                                       Event))))))))))))))
            :<|> (Named
                    "update-conversation-message-timer-unqualified"
                    (Summary "Update the message timer for a conversation (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied
                                                          'ModifyConversationMessageTimer)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("message-timer"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ConversationMessageTimerUpdate
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      (UpdateResponses
                                                                                         "Message timer unchanged"
                                                                                         "Message timer updated"
                                                                                         Event)
                                                                                      (UpdateResult
                                                                                         Event)))))))))))))))))
                  :<|> (Named
                          "update-conversation-message-timer"
                          (Summary "Update the message timer for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyConversationMessageTimer)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("message-timer"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationMessageTimerUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Message timer unchanged"
                                                                                       "Message timer updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event)))))))))))))))
                        :<|> (Named
                                "update-conversation-receipt-mode-unqualified"
                                (Summary "Update receipt mode for a conversation (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall
                                                       'Galley "update-conversation"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationReceiptMode)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("receipt-mode"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationReceiptModeUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Receipt mode unchanged"
                                                                                                         "Receipt mode updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-receipt-mode"
                                      (Summary "Update receipt mode for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Galley "update-conversation"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationReceiptMode)
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("receipt-mode"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 ConversationReceiptModeUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Receipt mode unchanged"
                                                                                                       "Receipt mode updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access-unqualified"
                                            (Summary
                                               "Update access modes for a conversation (deprecated)"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (Until 'V3
                                                             :> (Description
                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'ModifyConversationAccess)
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'RemoveConversationMember)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> (CanThrow
                                                                                                   'InvalidTargetAccess
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("access"
                                                                                                             :> (VersionedReqBody
                                                                                                                   'V2
                                                                                                                   '[JSON]
                                                                                                                   ConversationAccessData
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Access unchanged"
                                                                                                                         "Access updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event)))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access@v2"
                                                  (Summary "Update access modes for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (Until 'V3
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationAccess)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'InvalidTargetAccess
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("access"
                                                                                                               :> (VersionedReqBody
                                                                                                                     'V2
                                                                                                                     '[JSON]
                                                                                                                     ConversationAccessData
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Access unchanged"
                                                                                                                           "Access updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access"
                                                        (Summary
                                                           "Update access modes for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (From 'V3
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationAccess)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'InvalidTargetAccess
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("access"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationAccessData
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Access unchanged"
                                                                                                                                 "Access updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "get-conversation-self-unqualified"
                                                              (Summary
                                                                 "Get self membership properties (deprecated)"
                                                               :> (Deprecated
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("self"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (Maybe
                                                                                           Member)))))))
                                                            :<|> (Named
                                                                    "update-conversation-self-unqualified"
                                                                    (Summary
                                                                       "Update self membership properties (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("self"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           MemberUpdate
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "Update successful"]
                                                                                                              ()))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-self"
                                                                          (Summary
                                                                             "Update self membership properties"
                                                                           :> (Description
                                                                                 "**Note**: at least one field has to be provided."
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("self"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             MemberUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "Update successful"]
                                                                                                                ())))))))))
                                                                        :<|> Named
                                                                               "update-conversation-protocol"
                                                                               (Summary
                                                                                  "Update the protocol of the conversation"
                                                                                :> (From 'V5
                                                                                    :> (Description
                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                        :> (CanThrow
                                                                                              'ConvNotFound
                                                                                            :> (CanThrow
                                                                                                  'ConvInvalidProtocolTransition
                                                                                                :> (CanThrow
                                                                                                      ('ActionDenied
                                                                                                         'LeaveConversation)
                                                                                                    :> (CanThrow
                                                                                                          'InvalidOperation
                                                                                                        :> (CanThrow
                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (ZLocalUser
                                                                                                                            :> (ZConn
                                                                                                                                :> ("conversations"
                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                          '[Description
                                                                                                                                              "Conversation ID"]
                                                                                                                                          "cnv"
                                                                                                                                          ConvId
                                                                                                                                        :> ("protocol"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  ProtocolUpdate
                                                                                                                                                :> MultiVerb
                                                                                                                                                     'PUT
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                     (UpdateResult
                                                                                                                                                        Event))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-name-deprecated"
        (Summary "Update conversation name (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/name` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> (ReqBody '[JSON] ConversationRename
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  (UpdateResponses
                                                                     "Name unchanged"
                                                                     "Name updated"
                                                                     Event)
                                                                  (UpdateResult Event)))))))))))))))
      :<|> (Named
              "update-conversation-name-unqualified"
              (Summary "Update conversation name (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/name` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                       :> (CanThrow 'ConvNotFound
                                           :> (CanThrow 'InvalidOperation
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (Capture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("name"
                                                                   :> (ReqBody
                                                                         '[JSON] ConversationRename
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Name unchanged"
                                                                               "Name updated"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event))))))))))))))))
            :<|> (Named
                    "update-conversation-name"
                    (Summary "Update conversation name"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (QualifiedCapture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("name"
                                                                 :> (ReqBody
                                                                       '[JSON] ConversationRename
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          (UpdateResponses
                                                                             "Name updated"
                                                                             "Name unchanged"
                                                                             Event)
                                                                          (UpdateResult
                                                                             Event))))))))))))))
                  :<|> (Named
                          "update-conversation-message-timer-unqualified"
                          (Summary "Update the message timer for a conversation (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `/conversations/:domain/:cnv/message-timer` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'ModifyConversationMessageTimer)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("message-timer"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         ConversationMessageTimerUpdate
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            (UpdateResponses
                                                                                               "Message timer unchanged"
                                                                                               "Message timer updated"
                                                                                               Event)
                                                                                            (UpdateResult
                                                                                               Event)))))))))))))))))
                        :<|> (Named
                                "update-conversation-message-timer"
                                (Summary "Update the message timer for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyConversationMessageTimer)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("message-timer"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationMessageTimerUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Message timer unchanged"
                                                                                             "Message timer updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event)))))))))))))))
                              :<|> (Named
                                      "update-conversation-receipt-mode-unqualified"
                                      (Summary "Update receipt mode for a conversation (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                               :> (MakesFederatedCall
                                                     'Galley "on-conversation-updated"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-mls-message-sent"
                                                       :> (MakesFederatedCall
                                                             'Galley "update-conversation"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'ModifyConversationReceiptMode)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> ("conversations"
                                                                                           :> (Capture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("receipt-mode"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationReceiptModeUpdate
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Receipt mode unchanged"
                                                                                                               "Receipt mode updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-receipt-mode"
                                            (Summary "Update receipt mode for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall
                                                           'Galley "update-conversation"
                                                         :> (MakesFederatedCall
                                                               'Brig "get-users-by-ids"
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationReceiptMode)
                                                                         :> (CanThrow
                                                                               'ConvAccessDenied
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (CanThrow
                                                                                       'InvalidOperation
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("receipt-mode"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       ConversationReceiptModeUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Receipt mode unchanged"
                                                                                                             "Receipt mode updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access-unqualified"
                                                  (Summary
                                                     "Update access modes for a conversation (deprecated)"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (Until 'V3
                                                                   :> (Description
                                                                         "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'ModifyConversationAccess)
                                                                                   :> (CanThrow
                                                                                         ('ActionDenied
                                                                                            'RemoveConversationMember)
                                                                                       :> (CanThrow
                                                                                             'ConvAccessDenied
                                                                                           :> (CanThrow
                                                                                                 'ConvNotFound
                                                                                               :> (CanThrow
                                                                                                     'InvalidOperation
                                                                                                   :> (CanThrow
                                                                                                         'InvalidTargetAccess
                                                                                                       :> ("conversations"
                                                                                                           :> (Capture'
                                                                                                                 '[Description
                                                                                                                     "Conversation ID"]
                                                                                                                 "cnv"
                                                                                                                 ConvId
                                                                                                               :> ("access"
                                                                                                                   :> (VersionedReqBody
                                                                                                                         'V2
                                                                                                                         '[JSON]
                                                                                                                         ConversationAccessData
                                                                                                                       :> MultiVerb
                                                                                                                            'PUT
                                                                                                                            '[JSON]
                                                                                                                            (UpdateResponses
                                                                                                                               "Access unchanged"
                                                                                                                               "Access updated"
                                                                                                                               Event)
                                                                                                                            (UpdateResult
                                                                                                                               Event)))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access@v2"
                                                        (Summary
                                                           "Update access modes for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (Until 'V3
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationAccess)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'InvalidTargetAccess
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("access"
                                                                                                                     :> (VersionedReqBody
                                                                                                                           'V2
                                                                                                                           '[JSON]
                                                                                                                           ConversationAccessData
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Access unchanged"
                                                                                                                                 "Access updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "update-conversation-access"
                                                              (Summary
                                                                 "Update access modes for a conversation"
                                                               :> (MakesFederatedCall
                                                                     'Galley
                                                                     "on-conversation-updated"
                                                                   :> (MakesFederatedCall
                                                                         'Galley
                                                                         "on-mls-message-sent"
                                                                       :> (MakesFederatedCall
                                                                             'Brig
                                                                             "get-users-by-ids"
                                                                           :> (From 'V3
                                                                               :> (ZLocalUser
                                                                                   :> (ZConn
                                                                                       :> (CanThrow
                                                                                             ('ActionDenied
                                                                                                'ModifyConversationAccess)
                                                                                           :> (CanThrow
                                                                                                 ('ActionDenied
                                                                                                    'RemoveConversationMember)
                                                                                               :> (CanThrow
                                                                                                     'ConvAccessDenied
                                                                                                   :> (CanThrow
                                                                                                         'ConvNotFound
                                                                                                       :> (CanThrow
                                                                                                             'InvalidOperation
                                                                                                           :> (CanThrow
                                                                                                                 'InvalidTargetAccess
                                                                                                               :> ("conversations"
                                                                                                                   :> (QualifiedCapture'
                                                                                                                         '[Description
                                                                                                                             "Conversation ID"]
                                                                                                                         "cnv"
                                                                                                                         ConvId
                                                                                                                       :> ("access"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 ConversationAccessData
                                                                                                                               :> MultiVerb
                                                                                                                                    'PUT
                                                                                                                                    '[JSON]
                                                                                                                                    (UpdateResponses
                                                                                                                                       "Access unchanged"
                                                                                                                                       "Access updated"
                                                                                                                                       Event)
                                                                                                                                    (UpdateResult
                                                                                                                                       Event))))))))))))))))))
                                                            :<|> (Named
                                                                    "get-conversation-self-unqualified"
                                                                    (Summary
                                                                       "Get self membership properties (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (ZLocalUser
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("self"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (Maybe
                                                                                                 Member)))))))
                                                                  :<|> (Named
                                                                          "update-conversation-self-unqualified"
                                                                          (Summary
                                                                             "Update self membership properties (deprecated)"
                                                                           :> (Deprecated
                                                                               :> (Description
                                                                                     "Use `/conversations/:domain/:conv/self` instead."
                                                                                   :> (CanThrow
                                                                                         'ConvNotFound
                                                                                       :> (ZLocalUser
                                                                                           :> (ZConn
                                                                                               :> ("conversations"
                                                                                                   :> (Capture'
                                                                                                         '[Description
                                                                                                             "Conversation ID"]
                                                                                                         "cnv"
                                                                                                         ConvId
                                                                                                       :> ("self"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 MemberUpdate
                                                                                                               :> MultiVerb
                                                                                                                    'PUT
                                                                                                                    '[JSON]
                                                                                                                    '[RespondEmpty
                                                                                                                        200
                                                                                                                        "Update successful"]
                                                                                                                    ()))))))))))
                                                                        :<|> (Named
                                                                                "update-conversation-self"
                                                                                (Summary
                                                                                   "Update self membership properties"
                                                                                 :> (Description
                                                                                       "**Note**: at least one field has to be provided."
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (ZLocalUser
                                                                                             :> (ZConn
                                                                                                 :> ("conversations"
                                                                                                     :> (QualifiedCapture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("self"
                                                                                                             :> (ReqBody
                                                                                                                   '[JSON]
                                                                                                                   MemberUpdate
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      '[RespondEmpty
                                                                                                                          200
                                                                                                                          "Update successful"]
                                                                                                                      ())))))))))
                                                                              :<|> Named
                                                                                     "update-conversation-protocol"
                                                                                     (Summary
                                                                                        "Update the protocol of the conversation"
                                                                                      :> (From 'V5
                                                                                          :> (Description
                                                                                                "**Note**: Only proteus->mixed upgrade is supported."
                                                                                              :> (CanThrow
                                                                                                    'ConvNotFound
                                                                                                  :> (CanThrow
                                                                                                        'ConvInvalidProtocolTransition
                                                                                                      :> (CanThrow
                                                                                                            ('ActionDenied
                                                                                                               'LeaveConversation)
                                                                                                          :> (CanThrow
                                                                                                                'InvalidOperation
                                                                                                              :> (CanThrow
                                                                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                                                                  :> (CanThrow
                                                                                                                        'NotATeamMember
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> (ZLocalUser
                                                                                                                                  :> (ZConn
                                                                                                                                      :> ("conversations"
                                                                                                                                          :> (QualifiedCapture'
                                                                                                                                                '[Description
                                                                                                                                                    "Conversation ID"]
                                                                                                                                                "cnv"
                                                                                                                                                ConvId
                                                                                                                                              :> ("protocol"
                                                                                                                                                  :> (ReqBody
                                                                                                                                                        '[JSON]
                                                                                                                                                        ProtocolUpdate
                                                                                                                                                      :> MultiVerb
                                                                                                                                                           'PUT
                                                                                                                                                           '[JSON]
                                                                                                                                                           ConvUpdateResponses
                                                                                                                                                           (UpdateResult
                                                                                                                                                              Event)))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-name-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InvalidInput) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationName) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationRename
-> Sem r (UpdateResult Event)
updateUnqualifiedConversationName))
    API
  (Named
     "update-conversation-name-unqualified"
     (Summary "Update conversation name (deprecated)"
      :> (Deprecated
          :> (Description "Use `/conversations/:domain/:conv/name` instead."
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                      :> (MakesFederatedCall 'Brig "get-users-by-ids"
                          :> (CanThrow ('ActionDenied 'ModifyConversationName)
                              :> (CanThrow 'ConvNotFound
                                  :> (CanThrow 'InvalidOperation
                                      :> (ZLocalUser
                                          :> (ZConn
                                              :> ("conversations"
                                                  :> (Capture'
                                                        '[Description "Conversation ID"]
                                                        "cnv"
                                                        ConvId
                                                      :> ("name"
                                                          :> (ReqBody '[JSON] ConversationRename
                                                              :> MultiVerb
                                                                   'PUT
                                                                   '[JSON]
                                                                   (UpdateResponses
                                                                      "Name unchanged"
                                                                      "Name updated"
                                                                      Event)
                                                                   (UpdateResult
                                                                      Event)))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-name"
        (Summary "Update conversation name"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (CanThrow ('ActionDenied 'ModifyConversationName)
                         :> (CanThrow 'ConvNotFound
                             :> (CanThrow 'InvalidOperation
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (QualifiedCapture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("name"
                                                     :> (ReqBody '[JSON] ConversationRename
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              (UpdateResponses
                                                                 "Name updated"
                                                                 "Name unchanged"
                                                                 Event)
                                                              (UpdateResult Event))))))))))))))
      :<|> (Named
              "update-conversation-message-timer-unqualified"
              (Summary "Update the message timer for a conversation (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow
                                                 ('ActionDenied 'ModifyConversationMessageTimer)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("message-timer"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ConversationMessageTimerUpdate
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                (UpdateResponses
                                                                                   "Message timer unchanged"
                                                                                   "Message timer updated"
                                                                                   Event)
                                                                                (UpdateResult
                                                                                   Event)))))))))))))))))
            :<|> (Named
                    "update-conversation-message-timer"
                    (Summary "Update the message timer for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> (CanThrow
                                               ('ActionDenied 'ModifyConversationMessageTimer)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("message-timer"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationMessageTimerUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Message timer unchanged"
                                                                                 "Message timer updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event)))))))))))))))
                  :<|> (Named
                          "update-conversation-receipt-mode-unqualified"
                          (Summary "Update receipt mode for a conversation (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Galley "update-conversation"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationReceiptMode)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("receipt-mode"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationReceiptModeUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Receipt mode unchanged"
                                                                                                   "Receipt mode updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "update-conversation-receipt-mode"
                                (Summary "Update receipt mode for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Galley "update-conversation"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationReceiptMode)
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("receipt-mode"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           ConversationReceiptModeUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Receipt mode unchanged"
                                                                                                 "Receipt mode updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access-unqualified"
                                      (Summary "Update access modes for a conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (Until 'V3
                                                       :> (Description
                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'ModifyConversationAccess)
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'RemoveConversationMember)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> (CanThrow
                                                                                             'InvalidTargetAccess
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("access"
                                                                                                       :> (VersionedReqBody
                                                                                                             'V2
                                                                                                             '[JSON]
                                                                                                             ConversationAccessData
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Access unchanged"
                                                                                                                   "Access updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event)))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access@v2"
                                            (Summary "Update access modes for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (Until 'V3
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationAccess)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'InvalidTargetAccess
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("access"
                                                                                                         :> (VersionedReqBody
                                                                                                               'V2
                                                                                                               '[JSON]
                                                                                                               ConversationAccessData
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Access unchanged"
                                                                                                                     "Access updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access"
                                                  (Summary "Update access modes for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (From 'V3
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationAccess)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'InvalidTargetAccess
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("access"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationAccessData
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Access unchanged"
                                                                                                                           "Access updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "get-conversation-self-unqualified"
                                                        (Summary
                                                           "Get self membership properties (deprecated)"
                                                         :> (Deprecated
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("self"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (Maybe
                                                                                     Member)))))))
                                                      :<|> (Named
                                                              "update-conversation-self-unqualified"
                                                              (Summary
                                                                 "Update self membership properties (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("self"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     MemberUpdate
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "Update successful"]
                                                                                                        ()))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-self"
                                                                    (Summary
                                                                       "Update self membership properties"
                                                                     :> (Description
                                                                           "**Note**: at least one field has to be provided."
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("self"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       MemberUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "Update successful"]
                                                                                                          ())))))))))
                                                                  :<|> Named
                                                                         "update-conversation-protocol"
                                                                         (Summary
                                                                            "Update the protocol of the conversation"
                                                                          :> (From 'V5
                                                                              :> (Description
                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                  :> (CanThrow
                                                                                        'ConvNotFound
                                                                                      :> (CanThrow
                                                                                            'ConvInvalidProtocolTransition
                                                                                          :> (CanThrow
                                                                                                ('ActionDenied
                                                                                                   'LeaveConversation)
                                                                                              :> (CanThrow
                                                                                                    'InvalidOperation
                                                                                                  :> (CanThrow
                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (ZLocalUser
                                                                                                                      :> (ZConn
                                                                                                                          :> ("conversations"
                                                                                                                              :> (QualifiedCapture'
                                                                                                                                    '[Description
                                                                                                                                        "Conversation ID"]
                                                                                                                                    "cnv"
                                                                                                                                    ConvId
                                                                                                                                  :> ("protocol"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            ProtocolUpdate
                                                                                                                                          :> MultiVerb
                                                                                                                                               'PUT
                                                                                                                                               '[JSON]
                                                                                                                                               ConvUpdateResponses
                                                                                                                                               (UpdateResult
                                                                                                                                                  Event)))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-name-unqualified"
        (Summary "Update conversation name (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/name` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (CanThrow ('ActionDenied 'ModifyConversationName)
                                 :> (CanThrow 'ConvNotFound
                                     :> (CanThrow 'InvalidOperation
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (Capture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("name"
                                                             :> (ReqBody '[JSON] ConversationRename
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Name unchanged"
                                                                         "Name updated"
                                                                         Event)
                                                                      (UpdateResult
                                                                         Event))))))))))))))))
      :<|> (Named
              "update-conversation-name"
              (Summary "Update conversation name"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (CanThrow ('ActionDenied 'ModifyConversationName)
                               :> (CanThrow 'ConvNotFound
                                   :> (CanThrow 'InvalidOperation
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (QualifiedCapture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("name"
                                                           :> (ReqBody '[JSON] ConversationRename
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    (UpdateResponses
                                                                       "Name updated"
                                                                       "Name unchanged"
                                                                       Event)
                                                                    (UpdateResult
                                                                       Event))))))))))))))
            :<|> (Named
                    "update-conversation-message-timer-unqualified"
                    (Summary "Update the message timer for a conversation (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `/conversations/:domain/:cnv/message-timer` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied
                                                          'ModifyConversationMessageTimer)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("message-timer"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   ConversationMessageTimerUpdate
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      (UpdateResponses
                                                                                         "Message timer unchanged"
                                                                                         "Message timer updated"
                                                                                         Event)
                                                                                      (UpdateResult
                                                                                         Event)))))))))))))))))
                  :<|> (Named
                          "update-conversation-message-timer"
                          (Summary "Update the message timer for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyConversationMessageTimer)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("message-timer"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationMessageTimerUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Message timer unchanged"
                                                                                       "Message timer updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event)))))))))))))))
                        :<|> (Named
                                "update-conversation-receipt-mode-unqualified"
                                (Summary "Update receipt mode for a conversation (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                         :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                                 :> (MakesFederatedCall
                                                       'Galley "update-conversation"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'ModifyConversationReceiptMode)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> ("conversations"
                                                                                     :> (Capture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("receipt-mode"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationReceiptModeUpdate
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Receipt mode unchanged"
                                                                                                         "Receipt mode updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-receipt-mode"
                                      (Summary "Update receipt mode for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Galley "update-conversation"
                                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationReceiptMode)
                                                                   :> (CanThrow 'ConvAccessDenied
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (CanThrow
                                                                                 'InvalidOperation
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("receipt-mode"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 ConversationReceiptModeUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Receipt mode unchanged"
                                                                                                       "Receipt mode updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access-unqualified"
                                            (Summary
                                               "Update access modes for a conversation (deprecated)"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (Until 'V3
                                                             :> (Description
                                                                   "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'ModifyConversationAccess)
                                                                             :> (CanThrow
                                                                                   ('ActionDenied
                                                                                      'RemoveConversationMember)
                                                                                 :> (CanThrow
                                                                                       'ConvAccessDenied
                                                                                     :> (CanThrow
                                                                                           'ConvNotFound
                                                                                         :> (CanThrow
                                                                                               'InvalidOperation
                                                                                             :> (CanThrow
                                                                                                   'InvalidTargetAccess
                                                                                                 :> ("conversations"
                                                                                                     :> (Capture'
                                                                                                           '[Description
                                                                                                               "Conversation ID"]
                                                                                                           "cnv"
                                                                                                           ConvId
                                                                                                         :> ("access"
                                                                                                             :> (VersionedReqBody
                                                                                                                   'V2
                                                                                                                   '[JSON]
                                                                                                                   ConversationAccessData
                                                                                                                 :> MultiVerb
                                                                                                                      'PUT
                                                                                                                      '[JSON]
                                                                                                                      (UpdateResponses
                                                                                                                         "Access unchanged"
                                                                                                                         "Access updated"
                                                                                                                         Event)
                                                                                                                      (UpdateResult
                                                                                                                         Event)))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access@v2"
                                                  (Summary "Update access modes for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (Until 'V3
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationAccess)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'InvalidTargetAccess
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("access"
                                                                                                               :> (VersionedReqBody
                                                                                                                     'V2
                                                                                                                     '[JSON]
                                                                                                                     ConversationAccessData
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Access unchanged"
                                                                                                                           "Access updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "update-conversation-access"
                                                        (Summary
                                                           "Update access modes for a conversation"
                                                         :> (MakesFederatedCall
                                                               'Galley "on-conversation-updated"
                                                             :> (MakesFederatedCall
                                                                   'Galley "on-mls-message-sent"
                                                                 :> (MakesFederatedCall
                                                                       'Brig "get-users-by-ids"
                                                                     :> (From 'V3
                                                                         :> (ZLocalUser
                                                                             :> (ZConn
                                                                                 :> (CanThrow
                                                                                       ('ActionDenied
                                                                                          'ModifyConversationAccess)
                                                                                     :> (CanThrow
                                                                                           ('ActionDenied
                                                                                              'RemoveConversationMember)
                                                                                         :> (CanThrow
                                                                                               'ConvAccessDenied
                                                                                             :> (CanThrow
                                                                                                   'ConvNotFound
                                                                                                 :> (CanThrow
                                                                                                       'InvalidOperation
                                                                                                     :> (CanThrow
                                                                                                           'InvalidTargetAccess
                                                                                                         :> ("conversations"
                                                                                                             :> (QualifiedCapture'
                                                                                                                   '[Description
                                                                                                                       "Conversation ID"]
                                                                                                                   "cnv"
                                                                                                                   ConvId
                                                                                                                 :> ("access"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           ConversationAccessData
                                                                                                                         :> MultiVerb
                                                                                                                              'PUT
                                                                                                                              '[JSON]
                                                                                                                              (UpdateResponses
                                                                                                                                 "Access unchanged"
                                                                                                                                 "Access updated"
                                                                                                                                 Event)
                                                                                                                              (UpdateResult
                                                                                                                                 Event))))))))))))))))))
                                                      :<|> (Named
                                                              "get-conversation-self-unqualified"
                                                              (Summary
                                                                 "Get self membership properties (deprecated)"
                                                               :> (Deprecated
                                                                   :> (ZLocalUser
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("self"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (Maybe
                                                                                           Member)))))))
                                                            :<|> (Named
                                                                    "update-conversation-self-unqualified"
                                                                    (Summary
                                                                       "Update self membership properties (deprecated)"
                                                                     :> (Deprecated
                                                                         :> (Description
                                                                               "Use `/conversations/:domain/:conv/self` instead."
                                                                             :> (CanThrow
                                                                                   'ConvNotFound
                                                                                 :> (ZLocalUser
                                                                                     :> (ZConn
                                                                                         :> ("conversations"
                                                                                             :> (Capture'
                                                                                                   '[Description
                                                                                                       "Conversation ID"]
                                                                                                   "cnv"
                                                                                                   ConvId
                                                                                                 :> ("self"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           MemberUpdate
                                                                                                         :> MultiVerb
                                                                                                              'PUT
                                                                                                              '[JSON]
                                                                                                              '[RespondEmpty
                                                                                                                  200
                                                                                                                  "Update successful"]
                                                                                                              ()))))))))))
                                                                  :<|> (Named
                                                                          "update-conversation-self"
                                                                          (Summary
                                                                             "Update self membership properties"
                                                                           :> (Description
                                                                                 "**Note**: at least one field has to be provided."
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (ZLocalUser
                                                                                       :> (ZConn
                                                                                           :> ("conversations"
                                                                                               :> (QualifiedCapture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("self"
                                                                                                       :> (ReqBody
                                                                                                             '[JSON]
                                                                                                             MemberUpdate
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                '[RespondEmpty
                                                                                                                    200
                                                                                                                    "Update successful"]
                                                                                                                ())))))))))
                                                                        :<|> Named
                                                                               "update-conversation-protocol"
                                                                               (Summary
                                                                                  "Update the protocol of the conversation"
                                                                                :> (From 'V5
                                                                                    :> (Description
                                                                                          "**Note**: Only proteus->mixed upgrade is supported."
                                                                                        :> (CanThrow
                                                                                              'ConvNotFound
                                                                                            :> (CanThrow
                                                                                                  'ConvInvalidProtocolTransition
                                                                                                :> (CanThrow
                                                                                                      ('ActionDenied
                                                                                                         'LeaveConversation)
                                                                                                    :> (CanThrow
                                                                                                          'InvalidOperation
                                                                                                        :> (CanThrow
                                                                                                              'MLSMigrationCriteriaNotSatisfied
                                                                                                            :> (CanThrow
                                                                                                                  'NotATeamMember
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> (ZLocalUser
                                                                                                                            :> (ZConn
                                                                                                                                :> ("conversations"
                                                                                                                                    :> (QualifiedCapture'
                                                                                                                                          '[Description
                                                                                                                                              "Conversation ID"]
                                                                                                                                          "cnv"
                                                                                                                                          ConvId
                                                                                                                                        :> ("protocol"
                                                                                                                                            :> (ReqBody
                                                                                                                                                  '[JSON]
                                                                                                                                                  ProtocolUpdate
                                                                                                                                                :> MultiVerb
                                                                                                                                                     'PUT
                                                                                                                                                     '[JSON]
                                                                                                                                                     ConvUpdateResponses
                                                                                                                                                     (UpdateResult
                                                                                                                                                        Event))))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-name" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationRename
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationRename
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationName) ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InvalidInput) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationName) ())) r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member TeamStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationRename
-> Sem r (UpdateResult Event)
updateConversationName))
    API
  (Named
     "update-conversation-name"
     (Summary "Update conversation name"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Brig "get-users-by-ids"
                  :> (CanThrow ('ActionDenied 'ModifyConversationName)
                      :> (CanThrow 'ConvNotFound
                          :> (CanThrow 'InvalidOperation
                              :> (ZLocalUser
                                  :> (ZConn
                                      :> ("conversations"
                                          :> (QualifiedCapture'
                                                '[Description "Conversation ID"] "cnv" ConvId
                                              :> ("name"
                                                  :> (ReqBody '[JSON] ConversationRename
                                                      :> MultiVerb
                                                           'PUT
                                                           '[JSON]
                                                           (UpdateResponses
                                                              "Name updated" "Name unchanged" Event)
                                                           (UpdateResult Event)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-message-timer-unqualified"
        (Summary "Update the message timer for a conversation (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("message-timer"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       ConversationMessageTimerUpdate
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          (UpdateResponses
                                                                             "Message timer unchanged"
                                                                             "Message timer updated"
                                                                             Event)
                                                                          (UpdateResult
                                                                             Event)))))))))))))))))
      :<|> (Named
              "update-conversation-message-timer"
              (Summary "Update the message timer for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (ZLocalUser
                               :> (ZConn
                                   :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> ("conversations"
                                                       :> (QualifiedCapture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("message-timer"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     ConversationMessageTimerUpdate
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        (UpdateResponses
                                                                           "Message timer unchanged"
                                                                           "Message timer updated"
                                                                           Event)
                                                                        (UpdateResult
                                                                           Event)))))))))))))))
            :<|> (Named
                    "update-conversation-receipt-mode-unqualified"
                    (Summary "Update receipt mode for a conversation (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Galley "update-conversation"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyConversationReceiptMode)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("receipt-mode"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationReceiptModeUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Receipt mode unchanged"
                                                                                             "Receipt mode updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "update-conversation-receipt-mode"
                          (Summary "Update receipt mode for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Galley "update-conversation"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied
                                                            'ModifyConversationReceiptMode)
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("receipt-mode"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     ConversationReceiptModeUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Receipt mode unchanged"
                                                                                           "Receipt mode updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event))))))))))))))))
                        :<|> (Named
                                "update-conversation-access-unqualified"
                                (Summary "Update access modes for a conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (Until 'V3
                                                 :> (Description
                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'ModifyConversationAccess)
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'RemoveConversationMember)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> (CanThrow
                                                                                       'InvalidTargetAccess
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("access"
                                                                                                 :> (VersionedReqBody
                                                                                                       'V2
                                                                                                       '[JSON]
                                                                                                       ConversationAccessData
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Access unchanged"
                                                                                                             "Access updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event)))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access@v2"
                                      (Summary "Update access modes for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (Until 'V3
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationAccess)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'InvalidTargetAccess
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("access"
                                                                                                   :> (VersionedReqBody
                                                                                                         'V2
                                                                                                         '[JSON]
                                                                                                         ConversationAccessData
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Access unchanged"
                                                                                                               "Access updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access"
                                            (Summary "Update access modes for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (From 'V3
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationAccess)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'InvalidTargetAccess
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("access"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationAccessData
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Access unchanged"
                                                                                                                     "Access updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "get-conversation-self-unqualified"
                                                  (Summary
                                                     "Get self membership properties (deprecated)"
                                                   :> (Deprecated
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("self"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (Maybe Member)))))))
                                                :<|> (Named
                                                        "update-conversation-self-unqualified"
                                                        (Summary
                                                           "Update self membership properties (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("self"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               MemberUpdate
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "Update successful"]
                                                                                                  ()))))))))))
                                                      :<|> (Named
                                                              "update-conversation-self"
                                                              (Summary
                                                                 "Update self membership properties"
                                                               :> (Description
                                                                     "**Note**: at least one field has to be provided."
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("self"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 MemberUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "Update successful"]
                                                                                                    ())))))))))
                                                            :<|> Named
                                                                   "update-conversation-protocol"
                                                                   (Summary
                                                                      "Update the protocol of the conversation"
                                                                    :> (From 'V5
                                                                        :> (Description
                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                            :> (CanThrow
                                                                                  'ConvNotFound
                                                                                :> (CanThrow
                                                                                      'ConvInvalidProtocolTransition
                                                                                    :> (CanThrow
                                                                                          ('ActionDenied
                                                                                             'LeaveConversation)
                                                                                        :> (CanThrow
                                                                                              'InvalidOperation
                                                                                            :> (CanThrow
                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (ZLocalUser
                                                                                                                :> (ZConn
                                                                                                                    :> ("conversations"
                                                                                                                        :> (QualifiedCapture'
                                                                                                                              '[Description
                                                                                                                                  "Conversation ID"]
                                                                                                                              "cnv"
                                                                                                                              ConvId
                                                                                                                            :> ("protocol"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      ProtocolUpdate
                                                                                                                                    :> MultiVerb
                                                                                                                                         'PUT
                                                                                                                                         '[JSON]
                                                                                                                                         ConvUpdateResponses
                                                                                                                                         (UpdateResult
                                                                                                                                            Event))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-name"
        (Summary "Update conversation name"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (CanThrow ('ActionDenied 'ModifyConversationName)
                         :> (CanThrow 'ConvNotFound
                             :> (CanThrow 'InvalidOperation
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (QualifiedCapture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("name"
                                                     :> (ReqBody '[JSON] ConversationRename
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              (UpdateResponses
                                                                 "Name updated"
                                                                 "Name unchanged"
                                                                 Event)
                                                              (UpdateResult Event))))))))))))))
      :<|> (Named
              "update-conversation-message-timer-unqualified"
              (Summary "Update the message timer for a conversation (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `/conversations/:domain/:cnv/message-timer` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow
                                                 ('ActionDenied 'ModifyConversationMessageTimer)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("message-timer"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             ConversationMessageTimerUpdate
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                (UpdateResponses
                                                                                   "Message timer unchanged"
                                                                                   "Message timer updated"
                                                                                   Event)
                                                                                (UpdateResult
                                                                                   Event)))))))))))))))))
            :<|> (Named
                    "update-conversation-message-timer"
                    (Summary "Update the message timer for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> (CanThrow
                                               ('ActionDenied 'ModifyConversationMessageTimer)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("message-timer"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationMessageTimerUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Message timer unchanged"
                                                                                 "Message timer updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event)))))))))))))))
                  :<|> (Named
                          "update-conversation-receipt-mode-unqualified"
                          (Summary "Update receipt mode for a conversation (deprecated)"
                           :> (Deprecated
                               :> (Description
                                     "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                                   :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                       :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                           :> (MakesFederatedCall 'Galley "update-conversation"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'ModifyConversationReceiptMode)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> ("conversations"
                                                                               :> (Capture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("receipt-mode"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationReceiptModeUpdate
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Receipt mode unchanged"
                                                                                                   "Receipt mode updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "update-conversation-receipt-mode"
                                (Summary "Update receipt mode for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Galley "update-conversation"
                                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationReceiptMode)
                                                             :> (CanThrow 'ConvAccessDenied
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (CanThrow 'InvalidOperation
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("receipt-mode"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           ConversationReceiptModeUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Receipt mode unchanged"
                                                                                                 "Receipt mode updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access-unqualified"
                                      (Summary "Update access modes for a conversation (deprecated)"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (Until 'V3
                                                       :> (Description
                                                             "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'ModifyConversationAccess)
                                                                       :> (CanThrow
                                                                             ('ActionDenied
                                                                                'RemoveConversationMember)
                                                                           :> (CanThrow
                                                                                 'ConvAccessDenied
                                                                               :> (CanThrow
                                                                                     'ConvNotFound
                                                                                   :> (CanThrow
                                                                                         'InvalidOperation
                                                                                       :> (CanThrow
                                                                                             'InvalidTargetAccess
                                                                                           :> ("conversations"
                                                                                               :> (Capture'
                                                                                                     '[Description
                                                                                                         "Conversation ID"]
                                                                                                     "cnv"
                                                                                                     ConvId
                                                                                                   :> ("access"
                                                                                                       :> (VersionedReqBody
                                                                                                             'V2
                                                                                                             '[JSON]
                                                                                                             ConversationAccessData
                                                                                                           :> MultiVerb
                                                                                                                'PUT
                                                                                                                '[JSON]
                                                                                                                (UpdateResponses
                                                                                                                   "Access unchanged"
                                                                                                                   "Access updated"
                                                                                                                   Event)
                                                                                                                (UpdateResult
                                                                                                                   Event)))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access@v2"
                                            (Summary "Update access modes for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (Until 'V3
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationAccess)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'InvalidTargetAccess
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("access"
                                                                                                         :> (VersionedReqBody
                                                                                                               'V2
                                                                                                               '[JSON]
                                                                                                               ConversationAccessData
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Access unchanged"
                                                                                                                     "Access updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "update-conversation-access"
                                                  (Summary "Update access modes for a conversation"
                                                   :> (MakesFederatedCall
                                                         'Galley "on-conversation-updated"
                                                       :> (MakesFederatedCall
                                                             'Galley "on-mls-message-sent"
                                                           :> (MakesFederatedCall
                                                                 'Brig "get-users-by-ids"
                                                               :> (From 'V3
                                                                   :> (ZLocalUser
                                                                       :> (ZConn
                                                                           :> (CanThrow
                                                                                 ('ActionDenied
                                                                                    'ModifyConversationAccess)
                                                                               :> (CanThrow
                                                                                     ('ActionDenied
                                                                                        'RemoveConversationMember)
                                                                                   :> (CanThrow
                                                                                         'ConvAccessDenied
                                                                                       :> (CanThrow
                                                                                             'ConvNotFound
                                                                                           :> (CanThrow
                                                                                                 'InvalidOperation
                                                                                               :> (CanThrow
                                                                                                     'InvalidTargetAccess
                                                                                                   :> ("conversations"
                                                                                                       :> (QualifiedCapture'
                                                                                                             '[Description
                                                                                                                 "Conversation ID"]
                                                                                                             "cnv"
                                                                                                             ConvId
                                                                                                           :> ("access"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     ConversationAccessData
                                                                                                                   :> MultiVerb
                                                                                                                        'PUT
                                                                                                                        '[JSON]
                                                                                                                        (UpdateResponses
                                                                                                                           "Access unchanged"
                                                                                                                           "Access updated"
                                                                                                                           Event)
                                                                                                                        (UpdateResult
                                                                                                                           Event))))))))))))))))))
                                                :<|> (Named
                                                        "get-conversation-self-unqualified"
                                                        (Summary
                                                           "Get self membership properties (deprecated)"
                                                         :> (Deprecated
                                                             :> (ZLocalUser
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("self"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (Maybe
                                                                                     Member)))))))
                                                      :<|> (Named
                                                              "update-conversation-self-unqualified"
                                                              (Summary
                                                                 "Update self membership properties (deprecated)"
                                                               :> (Deprecated
                                                                   :> (Description
                                                                         "Use `/conversations/:domain/:conv/self` instead."
                                                                       :> (CanThrow 'ConvNotFound
                                                                           :> (ZLocalUser
                                                                               :> (ZConn
                                                                                   :> ("conversations"
                                                                                       :> (Capture'
                                                                                             '[Description
                                                                                                 "Conversation ID"]
                                                                                             "cnv"
                                                                                             ConvId
                                                                                           :> ("self"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     MemberUpdate
                                                                                                   :> MultiVerb
                                                                                                        'PUT
                                                                                                        '[JSON]
                                                                                                        '[RespondEmpty
                                                                                                            200
                                                                                                            "Update successful"]
                                                                                                        ()))))))))))
                                                            :<|> (Named
                                                                    "update-conversation-self"
                                                                    (Summary
                                                                       "Update self membership properties"
                                                                     :> (Description
                                                                           "**Note**: at least one field has to be provided."
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (ZLocalUser
                                                                                 :> (ZConn
                                                                                     :> ("conversations"
                                                                                         :> (QualifiedCapture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("self"
                                                                                                 :> (ReqBody
                                                                                                       '[JSON]
                                                                                                       MemberUpdate
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          '[RespondEmpty
                                                                                                              200
                                                                                                              "Update successful"]
                                                                                                          ())))))))))
                                                                  :<|> Named
                                                                         "update-conversation-protocol"
                                                                         (Summary
                                                                            "Update the protocol of the conversation"
                                                                          :> (From 'V5
                                                                              :> (Description
                                                                                    "**Note**: Only proteus->mixed upgrade is supported."
                                                                                  :> (CanThrow
                                                                                        'ConvNotFound
                                                                                      :> (CanThrow
                                                                                            'ConvInvalidProtocolTransition
                                                                                          :> (CanThrow
                                                                                                ('ActionDenied
                                                                                                   'LeaveConversation)
                                                                                              :> (CanThrow
                                                                                                    'InvalidOperation
                                                                                                  :> (CanThrow
                                                                                                        'MLSMigrationCriteriaNotSatisfied
                                                                                                      :> (CanThrow
                                                                                                            'NotATeamMember
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> (ZLocalUser
                                                                                                                      :> (ZConn
                                                                                                                          :> ("conversations"
                                                                                                                              :> (QualifiedCapture'
                                                                                                                                    '[Description
                                                                                                                                        "Conversation ID"]
                                                                                                                                    "cnv"
                                                                                                                                    ConvId
                                                                                                                                  :> ("protocol"
                                                                                                                                      :> (ReqBody
                                                                                                                                            '[JSON]
                                                                                                                                            ProtocolUpdate
                                                                                                                                          :> MultiVerb
                                                                                                                                               'PUT
                                                                                                                                               '[JSON]
                                                                                                                                               ConvUpdateResponses
                                                                                                                                               (UpdateResult
                                                                                                                                                  Event)))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-message-timer-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationMessageTimerUpdate
 -> Sem
      '[Error
          (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationMessageTimerUpdate
 -> Sem
      '[Error
          (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()))
   r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error FederationError) r, Member ExternalAccess r,
 Member NotificationSubsystem r, Member (Input UTCTime) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationMessageTimerUpdate
-> Sem r (UpdateResult Event)
updateConversationMessageTimerUnqualified))
    API
  (Named
     "update-conversation-message-timer-unqualified"
     (Summary "Update the message timer for a conversation (deprecated)"
      :> (Deprecated
          :> (Description
                "Use `/conversations/:domain/:cnv/message-timer` instead."
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                      :> (MakesFederatedCall 'Brig "get-users-by-ids"
                          :> (ZLocalUser
                              :> (ZConn
                                  :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'ConvNotFound
                                              :> (CanThrow 'InvalidOperation
                                                  :> ("conversations"
                                                      :> (Capture'
                                                            '[Description "Conversation ID"]
                                                            "cnv"
                                                            ConvId
                                                          :> ("message-timer"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    ConversationMessageTimerUpdate
                                                                  :> MultiVerb
                                                                       'PUT
                                                                       '[JSON]
                                                                       (UpdateResponses
                                                                          "Message timer unchanged"
                                                                          "Message timer updated"
                                                                          Event)
                                                                       (UpdateResult
                                                                          Event))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-message-timer"
        (Summary "Update the message timer for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (ZLocalUser
                         :> (ZConn
                             :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> ("conversations"
                                                 :> (QualifiedCapture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("message-timer"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               ConversationMessageTimerUpdate
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  (UpdateResponses
                                                                     "Message timer unchanged"
                                                                     "Message timer updated"
                                                                     Event)
                                                                  (UpdateResult Event)))))))))))))))
      :<|> (Named
              "update-conversation-receipt-mode-unqualified"
              (Summary "Update receipt mode for a conversation (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Galley "update-conversation"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyConversationReceiptMode)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("receipt-mode"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationReceiptModeUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Receipt mode unchanged"
                                                                                       "Receipt mode updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "update-conversation-receipt-mode"
                    (Summary "Update receipt mode for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Galley "update-conversation"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow
                                                   ('ActionDenied 'ModifyConversationReceiptMode)
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("receipt-mode"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               ConversationReceiptModeUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Receipt mode unchanged"
                                                                                     "Receipt mode updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event))))))))))))))))
                  :<|> (Named
                          "update-conversation-access-unqualified"
                          (Summary "Update access modes for a conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (Until 'V3
                                           :> (Description
                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'ModifyConversationAccess)
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'RemoveConversationMember)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> (CanThrow
                                                                                 'InvalidTargetAccess
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("access"
                                                                                           :> (VersionedReqBody
                                                                                                 'V2
                                                                                                 '[JSON]
                                                                                                 ConversationAccessData
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Access unchanged"
                                                                                                       "Access updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event)))))))))))))))))))
                        :<|> (Named
                                "update-conversation-access@v2"
                                (Summary "Update access modes for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationAccess)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'InvalidTargetAccess
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("access"
                                                                                             :> (VersionedReqBody
                                                                                                   'V2
                                                                                                   '[JSON]
                                                                                                   ConversationAccessData
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Access unchanged"
                                                                                                         "Access updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access"
                                      (Summary "Update access modes for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (From 'V3
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationAccess)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'InvalidTargetAccess
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("access"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationAccessData
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Access unchanged"
                                                                                                               "Access updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "get-conversation-self-unqualified"
                                            (Summary "Get self membership properties (deprecated)"
                                             :> (Deprecated
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("self"
                                                                 :> Get '[JSON] (Maybe Member)))))))
                                          :<|> (Named
                                                  "update-conversation-self-unqualified"
                                                  (Summary
                                                     "Update self membership properties (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("self"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         MemberUpdate
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "Update successful"]
                                                                                            ()))))))))))
                                                :<|> (Named
                                                        "update-conversation-self"
                                                        (Summary "Update self membership properties"
                                                         :> (Description
                                                               "**Note**: at least one field has to be provided."
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("self"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           MemberUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "Update successful"]
                                                                                              ())))))))))
                                                      :<|> Named
                                                             "update-conversation-protocol"
                                                             (Summary
                                                                "Update the protocol of the conversation"
                                                              :> (From 'V5
                                                                  :> (Description
                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                      :> (CanThrow 'ConvNotFound
                                                                          :> (CanThrow
                                                                                'ConvInvalidProtocolTransition
                                                                              :> (CanThrow
                                                                                    ('ActionDenied
                                                                                       'LeaveConversation)
                                                                                  :> (CanThrow
                                                                                        'InvalidOperation
                                                                                      :> (CanThrow
                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (ZLocalUser
                                                                                                          :> (ZConn
                                                                                                              :> ("conversations"
                                                                                                                  :> (QualifiedCapture'
                                                                                                                        '[Description
                                                                                                                            "Conversation ID"]
                                                                                                                        "cnv"
                                                                                                                        ConvId
                                                                                                                      :> ("protocol"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                ProtocolUpdate
                                                                                                                              :> MultiVerb
                                                                                                                                   'PUT
                                                                                                                                   '[JSON]
                                                                                                                                   ConvUpdateResponses
                                                                                                                                   (UpdateResult
                                                                                                                                      Event)))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-message-timer-unqualified"
        (Summary "Update the message timer for a conversation (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `/conversations/:domain/:cnv/message-timer` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("message-timer"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       ConversationMessageTimerUpdate
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          (UpdateResponses
                                                                             "Message timer unchanged"
                                                                             "Message timer updated"
                                                                             Event)
                                                                          (UpdateResult
                                                                             Event)))))))))))))))))
      :<|> (Named
              "update-conversation-message-timer"
              (Summary "Update the message timer for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (ZLocalUser
                               :> (ZConn
                                   :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                       :> (CanThrow 'ConvAccessDenied
                                           :> (CanThrow 'ConvNotFound
                                               :> (CanThrow 'InvalidOperation
                                                   :> ("conversations"
                                                       :> (QualifiedCapture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("message-timer"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     ConversationMessageTimerUpdate
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        (UpdateResponses
                                                                           "Message timer unchanged"
                                                                           "Message timer updated"
                                                                           Event)
                                                                        (UpdateResult
                                                                           Event)))))))))))))))
            :<|> (Named
                    "update-conversation-receipt-mode-unqualified"
                    (Summary "Update receipt mode for a conversation (deprecated)"
                     :> (Deprecated
                         :> (Description
                               "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                             :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                 :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                     :> (MakesFederatedCall 'Galley "update-conversation"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> (CanThrow
                                                           ('ActionDenied
                                                              'ModifyConversationReceiptMode)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> ("conversations"
                                                                         :> (Capture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("receipt-mode"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationReceiptModeUpdate
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Receipt mode unchanged"
                                                                                             "Receipt mode updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "update-conversation-receipt-mode"
                          (Summary "Update receipt mode for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Galley "update-conversation"
                                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied
                                                            'ModifyConversationReceiptMode)
                                                       :> (CanThrow 'ConvAccessDenied
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (CanThrow 'InvalidOperation
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("receipt-mode"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     ConversationReceiptModeUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Receipt mode unchanged"
                                                                                           "Receipt mode updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event))))))))))))))))
                        :<|> (Named
                                "update-conversation-access-unqualified"
                                (Summary "Update access modes for a conversation (deprecated)"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (Until 'V3
                                                 :> (Description
                                                       "Use PUT `/conversations/:domain/:cnv/access` instead."
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'ModifyConversationAccess)
                                                                 :> (CanThrow
                                                                       ('ActionDenied
                                                                          'RemoveConversationMember)
                                                                     :> (CanThrow 'ConvAccessDenied
                                                                         :> (CanThrow 'ConvNotFound
                                                                             :> (CanThrow
                                                                                   'InvalidOperation
                                                                                 :> (CanThrow
                                                                                       'InvalidTargetAccess
                                                                                     :> ("conversations"
                                                                                         :> (Capture'
                                                                                               '[Description
                                                                                                   "Conversation ID"]
                                                                                               "cnv"
                                                                                               ConvId
                                                                                             :> ("access"
                                                                                                 :> (VersionedReqBody
                                                                                                       'V2
                                                                                                       '[JSON]
                                                                                                       ConversationAccessData
                                                                                                     :> MultiVerb
                                                                                                          'PUT
                                                                                                          '[JSON]
                                                                                                          (UpdateResponses
                                                                                                             "Access unchanged"
                                                                                                             "Access updated"
                                                                                                             Event)
                                                                                                          (UpdateResult
                                                                                                             Event)))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access@v2"
                                      (Summary "Update access modes for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (Until 'V3
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationAccess)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'InvalidTargetAccess
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("access"
                                                                                                   :> (VersionedReqBody
                                                                                                         'V2
                                                                                                         '[JSON]
                                                                                                         ConversationAccessData
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Access unchanged"
                                                                                                               "Access updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "update-conversation-access"
                                            (Summary "Update access modes for a conversation"
                                             :> (MakesFederatedCall
                                                   'Galley "on-conversation-updated"
                                                 :> (MakesFederatedCall
                                                       'Galley "on-mls-message-sent"
                                                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                         :> (From 'V3
                                                             :> (ZLocalUser
                                                                 :> (ZConn
                                                                     :> (CanThrow
                                                                           ('ActionDenied
                                                                              'ModifyConversationAccess)
                                                                         :> (CanThrow
                                                                               ('ActionDenied
                                                                                  'RemoveConversationMember)
                                                                             :> (CanThrow
                                                                                   'ConvAccessDenied
                                                                                 :> (CanThrow
                                                                                       'ConvNotFound
                                                                                     :> (CanThrow
                                                                                           'InvalidOperation
                                                                                         :> (CanThrow
                                                                                               'InvalidTargetAccess
                                                                                             :> ("conversations"
                                                                                                 :> (QualifiedCapture'
                                                                                                       '[Description
                                                                                                           "Conversation ID"]
                                                                                                       "cnv"
                                                                                                       ConvId
                                                                                                     :> ("access"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               ConversationAccessData
                                                                                                             :> MultiVerb
                                                                                                                  'PUT
                                                                                                                  '[JSON]
                                                                                                                  (UpdateResponses
                                                                                                                     "Access unchanged"
                                                                                                                     "Access updated"
                                                                                                                     Event)
                                                                                                                  (UpdateResult
                                                                                                                     Event))))))))))))))))))
                                          :<|> (Named
                                                  "get-conversation-self-unqualified"
                                                  (Summary
                                                     "Get self membership properties (deprecated)"
                                                   :> (Deprecated
                                                       :> (ZLocalUser
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("self"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (Maybe Member)))))))
                                                :<|> (Named
                                                        "update-conversation-self-unqualified"
                                                        (Summary
                                                           "Update self membership properties (deprecated)"
                                                         :> (Deprecated
                                                             :> (Description
                                                                   "Use `/conversations/:domain/:conv/self` instead."
                                                                 :> (CanThrow 'ConvNotFound
                                                                     :> (ZLocalUser
                                                                         :> (ZConn
                                                                             :> ("conversations"
                                                                                 :> (Capture'
                                                                                       '[Description
                                                                                           "Conversation ID"]
                                                                                       "cnv"
                                                                                       ConvId
                                                                                     :> ("self"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               MemberUpdate
                                                                                             :> MultiVerb
                                                                                                  'PUT
                                                                                                  '[JSON]
                                                                                                  '[RespondEmpty
                                                                                                      200
                                                                                                      "Update successful"]
                                                                                                  ()))))))))))
                                                      :<|> (Named
                                                              "update-conversation-self"
                                                              (Summary
                                                                 "Update self membership properties"
                                                               :> (Description
                                                                     "**Note**: at least one field has to be provided."
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (ZLocalUser
                                                                           :> (ZConn
                                                                               :> ("conversations"
                                                                                   :> (QualifiedCapture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("self"
                                                                                           :> (ReqBody
                                                                                                 '[JSON]
                                                                                                 MemberUpdate
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    '[RespondEmpty
                                                                                                        200
                                                                                                        "Update successful"]
                                                                                                    ())))))))))
                                                            :<|> Named
                                                                   "update-conversation-protocol"
                                                                   (Summary
                                                                      "Update the protocol of the conversation"
                                                                    :> (From 'V5
                                                                        :> (Description
                                                                              "**Note**: Only proteus->mixed upgrade is supported."
                                                                            :> (CanThrow
                                                                                  'ConvNotFound
                                                                                :> (CanThrow
                                                                                      'ConvInvalidProtocolTransition
                                                                                    :> (CanThrow
                                                                                          ('ActionDenied
                                                                                             'LeaveConversation)
                                                                                        :> (CanThrow
                                                                                              'InvalidOperation
                                                                                            :> (CanThrow
                                                                                                  'MLSMigrationCriteriaNotSatisfied
                                                                                                :> (CanThrow
                                                                                                      'NotATeamMember
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> (ZLocalUser
                                                                                                                :> (ZConn
                                                                                                                    :> ("conversations"
                                                                                                                        :> (QualifiedCapture'
                                                                                                                              '[Description
                                                                                                                                  "Conversation ID"]
                                                                                                                              "cnv"
                                                                                                                              ConvId
                                                                                                                            :> ("protocol"
                                                                                                                                :> (ReqBody
                                                                                                                                      '[JSON]
                                                                                                                                      ProtocolUpdate
                                                                                                                                    :> MultiVerb
                                                                                                                                         'PUT
                                                                                                                                         '[JSON]
                                                                                                                                         ConvUpdateResponses
                                                                                                                                         (UpdateResult
                                                                                                                                            Event))))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-message-timer" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationMessageTimerUpdate
 -> Sem
      '[Error
          (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationMessageTimerUpdate
 -> Sem
      '[Error
          (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationMessageTimerUpdate
-> Sem
     '[Error
         (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r,
 Member ConversationStore r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationMessageTimer) ()))
   r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error FederationError) r, Member ExternalAccess r,
 Member NotificationSubsystem r, Member (Input UTCTime) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationMessageTimerUpdate
-> Sem r (UpdateResult Event)
updateConversationMessageTimer))
    API
  (Named
     "update-conversation-message-timer"
     (Summary "Update the message timer for a conversation"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Brig "get-users-by-ids"
                  :> (ZLocalUser
                      :> (ZConn
                          :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                              :> (CanThrow 'ConvAccessDenied
                                  :> (CanThrow 'ConvNotFound
                                      :> (CanThrow 'InvalidOperation
                                          :> ("conversations"
                                              :> (QualifiedCapture'
                                                    '[Description "Conversation ID"] "cnv" ConvId
                                                  :> ("message-timer"
                                                      :> (ReqBody
                                                            '[JSON] ConversationMessageTimerUpdate
                                                          :> MultiVerb
                                                               'PUT
                                                               '[JSON]
                                                               (UpdateResponses
                                                                  "Message timer unchanged"
                                                                  "Message timer updated"
                                                                  Event)
                                                               (UpdateResult Event))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-receipt-mode-unqualified"
        (Summary "Update receipt mode for a conversation (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Galley "update-conversation"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("receipt-mode"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationReceiptModeUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Receipt mode unchanged"
                                                                                 "Receipt mode updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "update-conversation-receipt-mode"
              (Summary "Update receipt mode for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Galley "update-conversation"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> ("conversations"
                                                           :> (QualifiedCapture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("receipt-mode"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         ConversationReceiptModeUpdate
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Receipt mode unchanged"
                                                                               "Receipt mode updated"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event))))))))))))))))
            :<|> (Named
                    "update-conversation-access-unqualified"
                    (Summary "Update access modes for a conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (Until 'V3
                                     :> (Description
                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied 'ModifyConversationAccess)
                                                     :> (CanThrow
                                                           ('ActionDenied 'RemoveConversationMember)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> (CanThrow
                                                                           'InvalidTargetAccess
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("access"
                                                                                     :> (VersionedReqBody
                                                                                           'V2
                                                                                           '[JSON]
                                                                                           ConversationAccessData
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Access unchanged"
                                                                                                 "Access updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event)))))))))))))))))))
                  :<|> (Named
                          "update-conversation-access@v2"
                          (Summary "Update access modes for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationAccess)
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'InvalidTargetAccess
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("access"
                                                                                       :> (VersionedReqBody
                                                                                             'V2
                                                                                             '[JSON]
                                                                                             ConversationAccessData
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Access unchanged"
                                                                                                   "Access updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "update-conversation-access"
                                (Summary "Update access modes for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (From 'V3
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationAccess)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'InvalidTargetAccess
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("access"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationAccessData
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Access unchanged"
                                                                                                         "Access updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "get-conversation-self-unqualified"
                                      (Summary "Get self membership properties (deprecated)"
                                       :> (Deprecated
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> (Capture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("self"
                                                           :> Get '[JSON] (Maybe Member)))))))
                                    :<|> (Named
                                            "update-conversation-self-unqualified"
                                            (Summary
                                               "Update self membership properties (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("self"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   MemberUpdate
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "Update successful"]
                                                                                      ()))))))))))
                                          :<|> (Named
                                                  "update-conversation-self"
                                                  (Summary "Update self membership properties"
                                                   :> (Description
                                                         "**Note**: at least one field has to be provided."
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("self"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     MemberUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "Update successful"]
                                                                                        ())))))))))
                                                :<|> Named
                                                       "update-conversation-protocol"
                                                       (Summary
                                                          "Update the protocol of the conversation"
                                                        :> (From 'V5
                                                            :> (Description
                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                :> (CanThrow 'ConvNotFound
                                                                    :> (CanThrow
                                                                          'ConvInvalidProtocolTransition
                                                                        :> (CanThrow
                                                                              ('ActionDenied
                                                                                 'LeaveConversation)
                                                                            :> (CanThrow
                                                                                  'InvalidOperation
                                                                                :> (CanThrow
                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (ZLocalUser
                                                                                                    :> (ZConn
                                                                                                        :> ("conversations"
                                                                                                            :> (QualifiedCapture'
                                                                                                                  '[Description
                                                                                                                      "Conversation ID"]
                                                                                                                  "cnv"
                                                                                                                  ConvId
                                                                                                                :> ("protocol"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          ProtocolUpdate
                                                                                                                        :> MultiVerb
                                                                                                                             'PUT
                                                                                                                             '[JSON]
                                                                                                                             ConvUpdateResponses
                                                                                                                             (UpdateResult
                                                                                                                                Event))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-message-timer"
        (Summary "Update the message timer for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (ZLocalUser
                         :> (ZConn
                             :> (CanThrow ('ActionDenied 'ModifyConversationMessageTimer)
                                 :> (CanThrow 'ConvAccessDenied
                                     :> (CanThrow 'ConvNotFound
                                         :> (CanThrow 'InvalidOperation
                                             :> ("conversations"
                                                 :> (QualifiedCapture'
                                                       '[Description "Conversation ID"] "cnv" ConvId
                                                     :> ("message-timer"
                                                         :> (ReqBody
                                                               '[JSON]
                                                               ConversationMessageTimerUpdate
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  (UpdateResponses
                                                                     "Message timer unchanged"
                                                                     "Message timer updated"
                                                                     Event)
                                                                  (UpdateResult Event)))))))))))))))
      :<|> (Named
              "update-conversation-receipt-mode-unqualified"
              (Summary "Update receipt mode for a conversation (deprecated)"
               :> (Deprecated
                   :> (Description
                         "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                               :> (MakesFederatedCall 'Galley "update-conversation"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> (CanThrow
                                                     ('ActionDenied 'ModifyConversationReceiptMode)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> ("conversations"
                                                                   :> (Capture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("receipt-mode"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationReceiptModeUpdate
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Receipt mode unchanged"
                                                                                       "Receipt mode updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "update-conversation-receipt-mode"
                    (Summary "Update receipt mode for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Galley "update-conversation"
                                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow
                                                   ('ActionDenied 'ModifyConversationReceiptMode)
                                                 :> (CanThrow 'ConvAccessDenied
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (CanThrow 'InvalidOperation
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("receipt-mode"
                                                                         :> (ReqBody
                                                                               '[JSON]
                                                                               ConversationReceiptModeUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Receipt mode unchanged"
                                                                                     "Receipt mode updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event))))))))))))))))
                  :<|> (Named
                          "update-conversation-access-unqualified"
                          (Summary "Update access modes for a conversation (deprecated)"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (Until 'V3
                                           :> (Description
                                                 "Use PUT `/conversations/:domain/:cnv/access` instead."
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'ModifyConversationAccess)
                                                           :> (CanThrow
                                                                 ('ActionDenied
                                                                    'RemoveConversationMember)
                                                               :> (CanThrow 'ConvAccessDenied
                                                                   :> (CanThrow 'ConvNotFound
                                                                       :> (CanThrow
                                                                             'InvalidOperation
                                                                           :> (CanThrow
                                                                                 'InvalidTargetAccess
                                                                               :> ("conversations"
                                                                                   :> (Capture'
                                                                                         '[Description
                                                                                             "Conversation ID"]
                                                                                         "cnv"
                                                                                         ConvId
                                                                                       :> ("access"
                                                                                           :> (VersionedReqBody
                                                                                                 'V2
                                                                                                 '[JSON]
                                                                                                 ConversationAccessData
                                                                                               :> MultiVerb
                                                                                                    'PUT
                                                                                                    '[JSON]
                                                                                                    (UpdateResponses
                                                                                                       "Access unchanged"
                                                                                                       "Access updated"
                                                                                                       Event)
                                                                                                    (UpdateResult
                                                                                                       Event)))))))))))))))))))
                        :<|> (Named
                                "update-conversation-access@v2"
                                (Summary "Update access modes for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (Until 'V3
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationAccess)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'InvalidTargetAccess
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("access"
                                                                                             :> (VersionedReqBody
                                                                                                   'V2
                                                                                                   '[JSON]
                                                                                                   ConversationAccessData
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Access unchanged"
                                                                                                         "Access updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "update-conversation-access"
                                      (Summary "Update access modes for a conversation"
                                       :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                           :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                               :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                                   :> (From 'V3
                                                       :> (ZLocalUser
                                                           :> (ZConn
                                                               :> (CanThrow
                                                                     ('ActionDenied
                                                                        'ModifyConversationAccess)
                                                                   :> (CanThrow
                                                                         ('ActionDenied
                                                                            'RemoveConversationMember)
                                                                       :> (CanThrow
                                                                             'ConvAccessDenied
                                                                           :> (CanThrow
                                                                                 'ConvNotFound
                                                                               :> (CanThrow
                                                                                     'InvalidOperation
                                                                                   :> (CanThrow
                                                                                         'InvalidTargetAccess
                                                                                       :> ("conversations"
                                                                                           :> (QualifiedCapture'
                                                                                                 '[Description
                                                                                                     "Conversation ID"]
                                                                                                 "cnv"
                                                                                                 ConvId
                                                                                               :> ("access"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         ConversationAccessData
                                                                                                       :> MultiVerb
                                                                                                            'PUT
                                                                                                            '[JSON]
                                                                                                            (UpdateResponses
                                                                                                               "Access unchanged"
                                                                                                               "Access updated"
                                                                                                               Event)
                                                                                                            (UpdateResult
                                                                                                               Event))))))))))))))))))
                                    :<|> (Named
                                            "get-conversation-self-unqualified"
                                            (Summary "Get self membership properties (deprecated)"
                                             :> (Deprecated
                                                 :> (ZLocalUser
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("self"
                                                                 :> Get '[JSON] (Maybe Member)))))))
                                          :<|> (Named
                                                  "update-conversation-self-unqualified"
                                                  (Summary
                                                     "Update self membership properties (deprecated)"
                                                   :> (Deprecated
                                                       :> (Description
                                                             "Use `/conversations/:domain/:conv/self` instead."
                                                           :> (CanThrow 'ConvNotFound
                                                               :> (ZLocalUser
                                                                   :> (ZConn
                                                                       :> ("conversations"
                                                                           :> (Capture'
                                                                                 '[Description
                                                                                     "Conversation ID"]
                                                                                 "cnv"
                                                                                 ConvId
                                                                               :> ("self"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         MemberUpdate
                                                                                       :> MultiVerb
                                                                                            'PUT
                                                                                            '[JSON]
                                                                                            '[RespondEmpty
                                                                                                200
                                                                                                "Update successful"]
                                                                                            ()))))))))))
                                                :<|> (Named
                                                        "update-conversation-self"
                                                        (Summary "Update self membership properties"
                                                         :> (Description
                                                               "**Note**: at least one field has to be provided."
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (ZLocalUser
                                                                     :> (ZConn
                                                                         :> ("conversations"
                                                                             :> (QualifiedCapture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("self"
                                                                                     :> (ReqBody
                                                                                           '[JSON]
                                                                                           MemberUpdate
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              '[RespondEmpty
                                                                                                  200
                                                                                                  "Update successful"]
                                                                                              ())))))))))
                                                      :<|> Named
                                                             "update-conversation-protocol"
                                                             (Summary
                                                                "Update the protocol of the conversation"
                                                              :> (From 'V5
                                                                  :> (Description
                                                                        "**Note**: Only proteus->mixed upgrade is supported."
                                                                      :> (CanThrow 'ConvNotFound
                                                                          :> (CanThrow
                                                                                'ConvInvalidProtocolTransition
                                                                              :> (CanThrow
                                                                                    ('ActionDenied
                                                                                       'LeaveConversation)
                                                                                  :> (CanThrow
                                                                                        'InvalidOperation
                                                                                      :> (CanThrow
                                                                                            'MLSMigrationCriteriaNotSatisfied
                                                                                          :> (CanThrow
                                                                                                'NotATeamMember
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> (ZLocalUser
                                                                                                          :> (ZConn
                                                                                                              :> ("conversations"
                                                                                                                  :> (QualifiedCapture'
                                                                                                                        '[Description
                                                                                                                            "Conversation ID"]
                                                                                                                        "cnv"
                                                                                                                        ConvId
                                                                                                                      :> ("protocol"
                                                                                                                          :> (ReqBody
                                                                                                                                '[JSON]
                                                                                                                                ProtocolUpdate
                                                                                                                              :> MultiVerb
                                                                                                                                   'PUT
                                                                                                                                   '[JSON]
                                                                                                                                   ConvUpdateResponses
                                                                                                                                   (UpdateResult
                                                                                                                                      Event)))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-receipt-mode-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "galley" "update-conversation",
    (HasAnnotation 'Remote "brig" "get-users-by-ids",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationReceiptModeUpdate
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "galley" "update-conversation")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationReceiptModeUpdate
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()))
   r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input (Local ())) r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationReceiptModeUpdate
-> Sem r (UpdateResult Event)
updateConversationReceiptModeUnqualified))
    API
  (Named
     "update-conversation-receipt-mode-unqualified"
     (Summary "Update receipt mode for a conversation (deprecated)"
      :> (Deprecated
          :> (Description
                "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
              :> (MakesFederatedCall 'Galley "on-conversation-updated"
                  :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                      :> (MakesFederatedCall 'Galley "update-conversation"
                          :> (MakesFederatedCall 'Brig "get-users-by-ids"
                              :> (ZLocalUser
                                  :> (ZConn
                                      :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                          :> (CanThrow 'ConvAccessDenied
                                              :> (CanThrow 'ConvNotFound
                                                  :> (CanThrow 'InvalidOperation
                                                      :> ("conversations"
                                                          :> (Capture'
                                                                '[Description "Conversation ID"]
                                                                "cnv"
                                                                ConvId
                                                              :> ("receipt-mode"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        ConversationReceiptModeUpdate
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           (UpdateResponses
                                                                              "Receipt mode unchanged"
                                                                              "Receipt mode updated"
                                                                              Event)
                                                                           (UpdateResult
                                                                              Event)))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-receipt-mode"
        (Summary "Update receipt mode for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Galley "update-conversation"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> ("conversations"
                                                     :> (QualifiedCapture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("receipt-mode"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   ConversationReceiptModeUpdate
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Receipt mode unchanged"
                                                                         "Receipt mode updated"
                                                                         Event)
                                                                      (UpdateResult
                                                                         Event))))))))))))))))
      :<|> (Named
              "update-conversation-access-unqualified"
              (Summary "Update access modes for a conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (Until 'V3
                               :> (Description
                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                               :> (CanThrow
                                                     ('ActionDenied 'RemoveConversationMember)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> (CanThrow 'InvalidTargetAccess
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("access"
                                                                               :> (VersionedReqBody
                                                                                     'V2
                                                                                     '[JSON]
                                                                                     ConversationAccessData
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Access unchanged"
                                                                                           "Access updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event)))))))))))))))))))
            :<|> (Named
                    "update-conversation-access@v2"
                    (Summary "Update access modes for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'InvalidTargetAccess
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("access"
                                                                                 :> (VersionedReqBody
                                                                                       'V2
                                                                                       '[JSON]
                                                                                       ConversationAccessData
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Access unchanged"
                                                                                             "Access updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "update-conversation-access"
                          (Summary "Update access modes for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (From 'V3
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationAccess)
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'InvalidTargetAccess
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("access"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationAccessData
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Access unchanged"
                                                                                                   "Access updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "get-conversation-self-unqualified"
                                (Summary "Get self membership properties (deprecated)"
                                 :> (Deprecated
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> (Capture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("self" :> Get '[JSON] (Maybe Member)))))))
                              :<|> (Named
                                      "update-conversation-self-unqualified"
                                      (Summary "Update self membership properties (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/self` instead."
                                               :> (CanThrow 'ConvNotFound
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("self"
                                                                       :> (ReqBody
                                                                             '[JSON] MemberUpdate
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "Update successful"]
                                                                                ()))))))))))
                                    :<|> (Named
                                            "update-conversation-self"
                                            (Summary "Update self membership properties"
                                             :> (Description
                                                   "**Note**: at least one field has to be provided."
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("self"
                                                                         :> (ReqBody
                                                                               '[JSON] MemberUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200
                                                                                      "Update successful"]
                                                                                  ())))))))))
                                          :<|> Named
                                                 "update-conversation-protocol"
                                                 (Summary "Update the protocol of the conversation"
                                                  :> (From 'V5
                                                      :> (Description
                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                          :> (CanThrow 'ConvNotFound
                                                              :> (CanThrow
                                                                    'ConvInvalidProtocolTransition
                                                                  :> (CanThrow
                                                                        ('ActionDenied
                                                                           'LeaveConversation)
                                                                      :> (CanThrow 'InvalidOperation
                                                                          :> (CanThrow
                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (ZLocalUser
                                                                                              :> (ZConn
                                                                                                  :> ("conversations"
                                                                                                      :> (QualifiedCapture'
                                                                                                            '[Description
                                                                                                                "Conversation ID"]
                                                                                                            "cnv"
                                                                                                            ConvId
                                                                                                          :> ("protocol"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    ProtocolUpdate
                                                                                                                  :> MultiVerb
                                                                                                                       'PUT
                                                                                                                       '[JSON]
                                                                                                                       ConvUpdateResponses
                                                                                                                       (UpdateResult
                                                                                                                          Event)))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-receipt-mode-unqualified"
        (Summary "Update receipt mode for a conversation (deprecated)"
         :> (Deprecated
             :> (Description
                   "Use `PUT /conversations/:domain/:cnv/receipt-mode` instead."
                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                         :> (MakesFederatedCall 'Galley "update-conversation"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> ("conversations"
                                                             :> (Capture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("receipt-mode"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationReceiptModeUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Receipt mode unchanged"
                                                                                 "Receipt mode updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "update-conversation-receipt-mode"
              (Summary "Update receipt mode for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Galley "update-conversation"
                           :> (MakesFederatedCall 'Brig "get-users-by-ids"
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                           :> (CanThrow 'ConvAccessDenied
                                               :> (CanThrow 'ConvNotFound
                                                   :> (CanThrow 'InvalidOperation
                                                       :> ("conversations"
                                                           :> (QualifiedCapture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("receipt-mode"
                                                                   :> (ReqBody
                                                                         '[JSON]
                                                                         ConversationReceiptModeUpdate
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            (UpdateResponses
                                                                               "Receipt mode unchanged"
                                                                               "Receipt mode updated"
                                                                               Event)
                                                                            (UpdateResult
                                                                               Event))))))))))))))))
            :<|> (Named
                    "update-conversation-access-unqualified"
                    (Summary "Update access modes for a conversation (deprecated)"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (Until 'V3
                                     :> (Description
                                           "Use PUT `/conversations/:domain/:cnv/access` instead."
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> (CanThrow
                                                       ('ActionDenied 'ModifyConversationAccess)
                                                     :> (CanThrow
                                                           ('ActionDenied 'RemoveConversationMember)
                                                         :> (CanThrow 'ConvAccessDenied
                                                             :> (CanThrow 'ConvNotFound
                                                                 :> (CanThrow 'InvalidOperation
                                                                     :> (CanThrow
                                                                           'InvalidTargetAccess
                                                                         :> ("conversations"
                                                                             :> (Capture'
                                                                                   '[Description
                                                                                       "Conversation ID"]
                                                                                   "cnv"
                                                                                   ConvId
                                                                                 :> ("access"
                                                                                     :> (VersionedReqBody
                                                                                           'V2
                                                                                           '[JSON]
                                                                                           ConversationAccessData
                                                                                         :> MultiVerb
                                                                                              'PUT
                                                                                              '[JSON]
                                                                                              (UpdateResponses
                                                                                                 "Access unchanged"
                                                                                                 "Access updated"
                                                                                                 Event)
                                                                                              (UpdateResult
                                                                                                 Event)))))))))))))))))))
                  :<|> (Named
                          "update-conversation-access@v2"
                          (Summary "Update access modes for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (Until 'V3
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationAccess)
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'InvalidTargetAccess
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("access"
                                                                                       :> (VersionedReqBody
                                                                                             'V2
                                                                                             '[JSON]
                                                                                             ConversationAccessData
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Access unchanged"
                                                                                                   "Access updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "update-conversation-access"
                                (Summary "Update access modes for a conversation"
                                 :> (MakesFederatedCall 'Galley "on-conversation-updated"
                                     :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                         :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                             :> (From 'V3
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> (CanThrow
                                                               ('ActionDenied
                                                                  'ModifyConversationAccess)
                                                             :> (CanThrow
                                                                   ('ActionDenied
                                                                      'RemoveConversationMember)
                                                                 :> (CanThrow 'ConvAccessDenied
                                                                     :> (CanThrow 'ConvNotFound
                                                                         :> (CanThrow
                                                                               'InvalidOperation
                                                                             :> (CanThrow
                                                                                   'InvalidTargetAccess
                                                                                 :> ("conversations"
                                                                                     :> (QualifiedCapture'
                                                                                           '[Description
                                                                                               "Conversation ID"]
                                                                                           "cnv"
                                                                                           ConvId
                                                                                         :> ("access"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   ConversationAccessData
                                                                                                 :> MultiVerb
                                                                                                      'PUT
                                                                                                      '[JSON]
                                                                                                      (UpdateResponses
                                                                                                         "Access unchanged"
                                                                                                         "Access updated"
                                                                                                         Event)
                                                                                                      (UpdateResult
                                                                                                         Event))))))))))))))))))
                              :<|> (Named
                                      "get-conversation-self-unqualified"
                                      (Summary "Get self membership properties (deprecated)"
                                       :> (Deprecated
                                           :> (ZLocalUser
                                               :> ("conversations"
                                                   :> (Capture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("self"
                                                           :> Get '[JSON] (Maybe Member)))))))
                                    :<|> (Named
                                            "update-conversation-self-unqualified"
                                            (Summary
                                               "Update self membership properties (deprecated)"
                                             :> (Deprecated
                                                 :> (Description
                                                       "Use `/conversations/:domain/:conv/self` instead."
                                                     :> (CanThrow 'ConvNotFound
                                                         :> (ZLocalUser
                                                             :> (ZConn
                                                                 :> ("conversations"
                                                                     :> (Capture'
                                                                           '[Description
                                                                               "Conversation ID"]
                                                                           "cnv"
                                                                           ConvId
                                                                         :> ("self"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   MemberUpdate
                                                                                 :> MultiVerb
                                                                                      'PUT
                                                                                      '[JSON]
                                                                                      '[RespondEmpty
                                                                                          200
                                                                                          "Update successful"]
                                                                                      ()))))))))))
                                          :<|> (Named
                                                  "update-conversation-self"
                                                  (Summary "Update self membership properties"
                                                   :> (Description
                                                         "**Note**: at least one field has to be provided."
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (ZLocalUser
                                                               :> (ZConn
                                                                   :> ("conversations"
                                                                       :> (QualifiedCapture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("self"
                                                                               :> (ReqBody
                                                                                     '[JSON]
                                                                                     MemberUpdate
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        '[RespondEmpty
                                                                                            200
                                                                                            "Update successful"]
                                                                                        ())))))))))
                                                :<|> Named
                                                       "update-conversation-protocol"
                                                       (Summary
                                                          "Update the protocol of the conversation"
                                                        :> (From 'V5
                                                            :> (Description
                                                                  "**Note**: Only proteus->mixed upgrade is supported."
                                                                :> (CanThrow 'ConvNotFound
                                                                    :> (CanThrow
                                                                          'ConvInvalidProtocolTransition
                                                                        :> (CanThrow
                                                                              ('ActionDenied
                                                                                 'LeaveConversation)
                                                                            :> (CanThrow
                                                                                  'InvalidOperation
                                                                                :> (CanThrow
                                                                                      'MLSMigrationCriteriaNotSatisfied
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> (ZLocalUser
                                                                                                    :> (ZConn
                                                                                                        :> ("conversations"
                                                                                                            :> (QualifiedCapture'
                                                                                                                  '[Description
                                                                                                                      "Conversation ID"]
                                                                                                                  "cnv"
                                                                                                                  ConvId
                                                                                                                :> ("protocol"
                                                                                                                    :> (ReqBody
                                                                                                                          '[JSON]
                                                                                                                          ProtocolUpdate
                                                                                                                        :> MultiVerb
                                                                                                                             'PUT
                                                                                                                             '[JSON]
                                                                                                                             ConvUpdateResponses
                                                                                                                             (UpdateResult
                                                                                                                                Event))))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-receipt-mode" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "galley" "update-conversation",
    (HasAnnotation 'Remote "brig" "get-users-by-ids",
     () :: Constraint)))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationReceiptModeUpdate
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "galley" "update-conversation")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationReceiptModeUpdate
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationReceiptModeUpdate
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member BackendNotificationQueueAccess r, Member BrigAccess r,
 Member ConversationStore r, Member (Error FederationError) r,
 Member (Error InternalError) r,
 Member
   (Error (Tagged ('ActionDenied 'ModifyConversationReceiptMode) ()))
   r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member ExternalAccess r, Member FederatorAccess r,
 Member NotificationSubsystem r, Member (Input (Local ())) r,
 Member (Input UTCTime) r, Member MemberStore r,
 Member (Logger (Msg -> Msg)) r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationReceiptModeUpdate
-> Sem r (UpdateResult Event)
updateConversationReceiptMode))
    API
  (Named
     "update-conversation-receipt-mode"
     (Summary "Update receipt mode for a conversation"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Galley "update-conversation"
                  :> (MakesFederatedCall 'Brig "get-users-by-ids"
                      :> (ZLocalUser
                          :> (ZConn
                              :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                  :> (CanThrow 'ConvAccessDenied
                                      :> (CanThrow 'ConvNotFound
                                          :> (CanThrow 'InvalidOperation
                                              :> ("conversations"
                                                  :> (QualifiedCapture'
                                                        '[Description "Conversation ID"]
                                                        "cnv"
                                                        ConvId
                                                      :> ("receipt-mode"
                                                          :> (ReqBody
                                                                '[JSON]
                                                                ConversationReceiptModeUpdate
                                                              :> MultiVerb
                                                                   'PUT
                                                                   '[JSON]
                                                                   (UpdateResponses
                                                                      "Receipt mode unchanged"
                                                                      "Receipt mode updated"
                                                                      Event)
                                                                   (UpdateResult
                                                                      Event)))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-access-unqualified"
        (Summary "Update access modes for a conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (Until 'V3
                         :> (Description
                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                         :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> (CanThrow 'InvalidTargetAccess
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("access"
                                                                         :> (VersionedReqBody
                                                                               'V2
                                                                               '[JSON]
                                                                               ConversationAccessData
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Access unchanged"
                                                                                     "Access updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event)))))))))))))))))))
      :<|> (Named
              "update-conversation-access@v2"
              (Summary "Update access modes for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'InvalidTargetAccess
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("access"
                                                                           :> (VersionedReqBody
                                                                                 'V2
                                                                                 '[JSON]
                                                                                 ConversationAccessData
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Access unchanged"
                                                                                       "Access updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "update-conversation-access"
                    (Summary "Update access modes for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (From 'V3
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'InvalidTargetAccess
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("access"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationAccessData
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Access unchanged"
                                                                                             "Access updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "get-conversation-self-unqualified"
                          (Summary "Get self membership properties (deprecated)"
                           :> (Deprecated
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("self" :> Get '[JSON] (Maybe Member)))))))
                        :<|> (Named
                                "update-conversation-self-unqualified"
                                (Summary "Update self membership properties (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/self` instead."
                                         :> (CanThrow 'ConvNotFound
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("self"
                                                                 :> (ReqBody '[JSON] MemberUpdate
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          '[RespondEmpty
                                                                              200
                                                                              "Update successful"]
                                                                          ()))))))))))
                              :<|> (Named
                                      "update-conversation-self"
                                      (Summary "Update self membership properties"
                                       :> (Description
                                             "**Note**: at least one field has to be provided."
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (QualifiedCapture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("self"
                                                                   :> (ReqBody '[JSON] MemberUpdate
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            '[RespondEmpty
                                                                                200
                                                                                "Update successful"]
                                                                            ())))))))))
                                    :<|> Named
                                           "update-conversation-protocol"
                                           (Summary "Update the protocol of the conversation"
                                            :> (From 'V5
                                                :> (Description
                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                    :> (CanThrow 'ConvNotFound
                                                        :> (CanThrow 'ConvInvalidProtocolTransition
                                                            :> (CanThrow
                                                                  ('ActionDenied 'LeaveConversation)
                                                                :> (CanThrow 'InvalidOperation
                                                                    :> (CanThrow
                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (ZLocalUser
                                                                                        :> (ZConn
                                                                                            :> ("conversations"
                                                                                                :> (QualifiedCapture'
                                                                                                      '[Description
                                                                                                          "Conversation ID"]
                                                                                                      "cnv"
                                                                                                      ConvId
                                                                                                    :> ("protocol"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              ProtocolUpdate
                                                                                                            :> MultiVerb
                                                                                                                 'PUT
                                                                                                                 '[JSON]
                                                                                                                 ConvUpdateResponses
                                                                                                                 (UpdateResult
                                                                                                                    Event))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-receipt-mode"
        (Summary "Update receipt mode for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Galley "update-conversation"
                     :> (MakesFederatedCall 'Brig "get-users-by-ids"
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationReceiptMode)
                                     :> (CanThrow 'ConvAccessDenied
                                         :> (CanThrow 'ConvNotFound
                                             :> (CanThrow 'InvalidOperation
                                                 :> ("conversations"
                                                     :> (QualifiedCapture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("receipt-mode"
                                                             :> (ReqBody
                                                                   '[JSON]
                                                                   ConversationReceiptModeUpdate
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      (UpdateResponses
                                                                         "Receipt mode unchanged"
                                                                         "Receipt mode updated"
                                                                         Event)
                                                                      (UpdateResult
                                                                         Event))))))))))))))))
      :<|> (Named
              "update-conversation-access-unqualified"
              (Summary "Update access modes for a conversation (deprecated)"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (Until 'V3
                               :> (Description
                                     "Use PUT `/conversations/:domain/:cnv/access` instead."
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                               :> (CanThrow
                                                     ('ActionDenied 'RemoveConversationMember)
                                                   :> (CanThrow 'ConvAccessDenied
                                                       :> (CanThrow 'ConvNotFound
                                                           :> (CanThrow 'InvalidOperation
                                                               :> (CanThrow 'InvalidTargetAccess
                                                                   :> ("conversations"
                                                                       :> (Capture'
                                                                             '[Description
                                                                                 "Conversation ID"]
                                                                             "cnv"
                                                                             ConvId
                                                                           :> ("access"
                                                                               :> (VersionedReqBody
                                                                                     'V2
                                                                                     '[JSON]
                                                                                     ConversationAccessData
                                                                                   :> MultiVerb
                                                                                        'PUT
                                                                                        '[JSON]
                                                                                        (UpdateResponses
                                                                                           "Access unchanged"
                                                                                           "Access updated"
                                                                                           Event)
                                                                                        (UpdateResult
                                                                                           Event)))))))))))))))))))
            :<|> (Named
                    "update-conversation-access@v2"
                    (Summary "Update access modes for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (Until 'V3
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'InvalidTargetAccess
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("access"
                                                                                 :> (VersionedReqBody
                                                                                       'V2
                                                                                       '[JSON]
                                                                                       ConversationAccessData
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Access unchanged"
                                                                                             "Access updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "update-conversation-access"
                          (Summary "Update access modes for a conversation"
                           :> (MakesFederatedCall 'Galley "on-conversation-updated"
                               :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                                   :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                       :> (From 'V3
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> (CanThrow
                                                         ('ActionDenied 'ModifyConversationAccess)
                                                       :> (CanThrow
                                                             ('ActionDenied
                                                                'RemoveConversationMember)
                                                           :> (CanThrow 'ConvAccessDenied
                                                               :> (CanThrow 'ConvNotFound
                                                                   :> (CanThrow 'InvalidOperation
                                                                       :> (CanThrow
                                                                             'InvalidTargetAccess
                                                                           :> ("conversations"
                                                                               :> (QualifiedCapture'
                                                                                     '[Description
                                                                                         "Conversation ID"]
                                                                                     "cnv"
                                                                                     ConvId
                                                                                   :> ("access"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             ConversationAccessData
                                                                                           :> MultiVerb
                                                                                                'PUT
                                                                                                '[JSON]
                                                                                                (UpdateResponses
                                                                                                   "Access unchanged"
                                                                                                   "Access updated"
                                                                                                   Event)
                                                                                                (UpdateResult
                                                                                                   Event))))))))))))))))))
                        :<|> (Named
                                "get-conversation-self-unqualified"
                                (Summary "Get self membership properties (deprecated)"
                                 :> (Deprecated
                                     :> (ZLocalUser
                                         :> ("conversations"
                                             :> (Capture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("self" :> Get '[JSON] (Maybe Member)))))))
                              :<|> (Named
                                      "update-conversation-self-unqualified"
                                      (Summary "Update self membership properties (deprecated)"
                                       :> (Deprecated
                                           :> (Description
                                                 "Use `/conversations/:domain/:conv/self` instead."
                                               :> (CanThrow 'ConvNotFound
                                                   :> (ZLocalUser
                                                       :> (ZConn
                                                           :> ("conversations"
                                                               :> (Capture'
                                                                     '[Description
                                                                         "Conversation ID"]
                                                                     "cnv"
                                                                     ConvId
                                                                   :> ("self"
                                                                       :> (ReqBody
                                                                             '[JSON] MemberUpdate
                                                                           :> MultiVerb
                                                                                'PUT
                                                                                '[JSON]
                                                                                '[RespondEmpty
                                                                                    200
                                                                                    "Update successful"]
                                                                                ()))))))))))
                                    :<|> (Named
                                            "update-conversation-self"
                                            (Summary "Update self membership properties"
                                             :> (Description
                                                   "**Note**: at least one field has to be provided."
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (ZLocalUser
                                                         :> (ZConn
                                                             :> ("conversations"
                                                                 :> (QualifiedCapture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("self"
                                                                         :> (ReqBody
                                                                               '[JSON] MemberUpdate
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  '[RespondEmpty
                                                                                      200
                                                                                      "Update successful"]
                                                                                  ())))))))))
                                          :<|> Named
                                                 "update-conversation-protocol"
                                                 (Summary "Update the protocol of the conversation"
                                                  :> (From 'V5
                                                      :> (Description
                                                            "**Note**: Only proteus->mixed upgrade is supported."
                                                          :> (CanThrow 'ConvNotFound
                                                              :> (CanThrow
                                                                    'ConvInvalidProtocolTransition
                                                                  :> (CanThrow
                                                                        ('ActionDenied
                                                                           'LeaveConversation)
                                                                      :> (CanThrow 'InvalidOperation
                                                                          :> (CanThrow
                                                                                'MLSMigrationCriteriaNotSatisfied
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> (ZLocalUser
                                                                                              :> (ZConn
                                                                                                  :> ("conversations"
                                                                                                      :> (QualifiedCapture'
                                                                                                            '[Description
                                                                                                                "Conversation ID"]
                                                                                                            "cnv"
                                                                                                            ConvId
                                                                                                          :> ("protocol"
                                                                                                              :> (ReqBody
                                                                                                                    '[JSON]
                                                                                                                    ProtocolUpdate
                                                                                                                  :> MultiVerb
                                                                                                                       'PUT
                                                                                                                       '[JSON]
                                                                                                                       ConvUpdateResponses
                                                                                                                       (UpdateResult
                                                                                                                          Event)))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-access-unqualified" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
Members UpdateConversationAccessEffects r =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> ConversationAccessData
-> Sem r (UpdateResult Event)
updateConversationAccessUnqualified))
    API
  (Named
     "update-conversation-access-unqualified"
     (Summary "Update access modes for a conversation (deprecated)"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Brig "get-users-by-ids"
                  :> (Until 'V3
                      :> (Description
                            "Use PUT `/conversations/:domain/:cnv/access` instead."
                          :> (ZLocalUser
                              :> (ZConn
                                  :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                      :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                          :> (CanThrow 'ConvAccessDenied
                                              :> (CanThrow 'ConvNotFound
                                                  :> (CanThrow 'InvalidOperation
                                                      :> (CanThrow 'InvalidTargetAccess
                                                          :> ("conversations"
                                                              :> (Capture'
                                                                    '[Description "Conversation ID"]
                                                                    "cnv"
                                                                    ConvId
                                                                  :> ("access"
                                                                      :> (VersionedReqBody
                                                                            'V2
                                                                            '[JSON]
                                                                            ConversationAccessData
                                                                          :> MultiVerb
                                                                               'PUT
                                                                               '[JSON]
                                                                               (UpdateResponses
                                                                                  "Access unchanged"
                                                                                  "Access updated"
                                                                                  Event)
                                                                               (UpdateResult
                                                                                  Event))))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-access@v2"
        (Summary "Update access modes for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'InvalidTargetAccess
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("access"
                                                                     :> (VersionedReqBody
                                                                           'V2
                                                                           '[JSON]
                                                                           ConversationAccessData
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Access unchanged"
                                                                                 "Access updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "update-conversation-access"
              (Summary "Update access modes for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (From 'V3
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'InvalidTargetAccess
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("access"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationAccessData
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Access unchanged"
                                                                                       "Access updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "get-conversation-self-unqualified"
                    (Summary "Get self membership properties (deprecated)"
                     :> (Deprecated
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("self" :> Get '[JSON] (Maybe Member)))))))
                  :<|> (Named
                          "update-conversation-self-unqualified"
                          (Summary "Update self membership properties (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/self` instead."
                                   :> (CanThrow 'ConvNotFound
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (Capture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("self"
                                                           :> (ReqBody '[JSON] MemberUpdate
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    '[RespondEmpty
                                                                        200 "Update successful"]
                                                                    ()))))))))))
                        :<|> (Named
                                "update-conversation-self"
                                (Summary "Update self membership properties"
                                 :> (Description "**Note**: at least one field has to be provided."
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (QualifiedCapture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("self"
                                                             :> (ReqBody '[JSON] MemberUpdate
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      '[RespondEmpty
                                                                          200 "Update successful"]
                                                                      ())))))))))
                              :<|> Named
                                     "update-conversation-protocol"
                                     (Summary "Update the protocol of the conversation"
                                      :> (From 'V5
                                          :> (Description
                                                "**Note**: Only proteus->mixed upgrade is supported."
                                              :> (CanThrow 'ConvNotFound
                                                  :> (CanThrow 'ConvInvalidProtocolTransition
                                                      :> (CanThrow
                                                            ('ActionDenied 'LeaveConversation)
                                                          :> (CanThrow 'InvalidOperation
                                                              :> (CanThrow
                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (ZLocalUser
                                                                                  :> (ZConn
                                                                                      :> ("conversations"
                                                                                          :> (QualifiedCapture'
                                                                                                '[Description
                                                                                                    "Conversation ID"]
                                                                                                "cnv"
                                                                                                ConvId
                                                                                              :> ("protocol"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        ProtocolUpdate
                                                                                                      :> MultiVerb
                                                                                                           'PUT
                                                                                                           '[JSON]
                                                                                                           ConvUpdateResponses
                                                                                                           (UpdateResult
                                                                                                              Event)))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-access-unqualified"
        (Summary "Update access modes for a conversation (deprecated)"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (Until 'V3
                         :> (Description
                               "Use PUT `/conversations/:domain/:cnv/access` instead."
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                         :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                             :> (CanThrow 'ConvAccessDenied
                                                 :> (CanThrow 'ConvNotFound
                                                     :> (CanThrow 'InvalidOperation
                                                         :> (CanThrow 'InvalidTargetAccess
                                                             :> ("conversations"
                                                                 :> (Capture'
                                                                       '[Description
                                                                           "Conversation ID"]
                                                                       "cnv"
                                                                       ConvId
                                                                     :> ("access"
                                                                         :> (VersionedReqBody
                                                                               'V2
                                                                               '[JSON]
                                                                               ConversationAccessData
                                                                             :> MultiVerb
                                                                                  'PUT
                                                                                  '[JSON]
                                                                                  (UpdateResponses
                                                                                     "Access unchanged"
                                                                                     "Access updated"
                                                                                     Event)
                                                                                  (UpdateResult
                                                                                     Event)))))))))))))))))))
      :<|> (Named
              "update-conversation-access@v2"
              (Summary "Update access modes for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (Until 'V3
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'InvalidTargetAccess
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("access"
                                                                           :> (VersionedReqBody
                                                                                 'V2
                                                                                 '[JSON]
                                                                                 ConversationAccessData
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Access unchanged"
                                                                                       "Access updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "update-conversation-access"
                    (Summary "Update access modes for a conversation"
                     :> (MakesFederatedCall 'Galley "on-conversation-updated"
                         :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                             :> (MakesFederatedCall 'Brig "get-users-by-ids"
                                 :> (From 'V3
                                     :> (ZLocalUser
                                         :> (ZConn
                                             :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                                 :> (CanThrow
                                                       ('ActionDenied 'RemoveConversationMember)
                                                     :> (CanThrow 'ConvAccessDenied
                                                         :> (CanThrow 'ConvNotFound
                                                             :> (CanThrow 'InvalidOperation
                                                                 :> (CanThrow 'InvalidTargetAccess
                                                                     :> ("conversations"
                                                                         :> (QualifiedCapture'
                                                                               '[Description
                                                                                   "Conversation ID"]
                                                                               "cnv"
                                                                               ConvId
                                                                             :> ("access"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       ConversationAccessData
                                                                                     :> MultiVerb
                                                                                          'PUT
                                                                                          '[JSON]
                                                                                          (UpdateResponses
                                                                                             "Access unchanged"
                                                                                             "Access updated"
                                                                                             Event)
                                                                                          (UpdateResult
                                                                                             Event))))))))))))))))))
                  :<|> (Named
                          "get-conversation-self-unqualified"
                          (Summary "Get self membership properties (deprecated)"
                           :> (Deprecated
                               :> (ZLocalUser
                                   :> ("conversations"
                                       :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("self" :> Get '[JSON] (Maybe Member)))))))
                        :<|> (Named
                                "update-conversation-self-unqualified"
                                (Summary "Update self membership properties (deprecated)"
                                 :> (Deprecated
                                     :> (Description
                                           "Use `/conversations/:domain/:conv/self` instead."
                                         :> (CanThrow 'ConvNotFound
                                             :> (ZLocalUser
                                                 :> (ZConn
                                                     :> ("conversations"
                                                         :> (Capture'
                                                               '[Description "Conversation ID"]
                                                               "cnv"
                                                               ConvId
                                                             :> ("self"
                                                                 :> (ReqBody '[JSON] MemberUpdate
                                                                     :> MultiVerb
                                                                          'PUT
                                                                          '[JSON]
                                                                          '[RespondEmpty
                                                                              200
                                                                              "Update successful"]
                                                                          ()))))))))))
                              :<|> (Named
                                      "update-conversation-self"
                                      (Summary "Update self membership properties"
                                       :> (Description
                                             "**Note**: at least one field has to be provided."
                                           :> (CanThrow 'ConvNotFound
                                               :> (ZLocalUser
                                                   :> (ZConn
                                                       :> ("conversations"
                                                           :> (QualifiedCapture'
                                                                 '[Description "Conversation ID"]
                                                                 "cnv"
                                                                 ConvId
                                                               :> ("self"
                                                                   :> (ReqBody '[JSON] MemberUpdate
                                                                       :> MultiVerb
                                                                            'PUT
                                                                            '[JSON]
                                                                            '[RespondEmpty
                                                                                200
                                                                                "Update successful"]
                                                                            ())))))))))
                                    :<|> Named
                                           "update-conversation-protocol"
                                           (Summary "Update the protocol of the conversation"
                                            :> (From 'V5
                                                :> (Description
                                                      "**Note**: Only proteus->mixed upgrade is supported."
                                                    :> (CanThrow 'ConvNotFound
                                                        :> (CanThrow 'ConvInvalidProtocolTransition
                                                            :> (CanThrow
                                                                  ('ActionDenied 'LeaveConversation)
                                                                :> (CanThrow 'InvalidOperation
                                                                    :> (CanThrow
                                                                          'MLSMigrationCriteriaNotSatisfied
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> (ZLocalUser
                                                                                        :> (ZConn
                                                                                            :> ("conversations"
                                                                                                :> (QualifiedCapture'
                                                                                                      '[Description
                                                                                                          "Conversation ID"]
                                                                                                      "cnv"
                                                                                                      ConvId
                                                                                                    :> ("protocol"
                                                                                                        :> (ReqBody
                                                                                                              '[JSON]
                                                                                                              ProtocolUpdate
                                                                                                            :> MultiVerb
                                                                                                                 'PUT
                                                                                                                 '[JSON]
                                                                                                                 ConvUpdateResponses
                                                                                                                 (UpdateResult
                                                                                                                    Event))))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-access@v2" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
Members UpdateConversationAccessEffects r =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem r (UpdateResult Event)
updateConversationAccess))
    API
  (Named
     "update-conversation-access@v2"
     (Summary "Update access modes for a conversation"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Brig "get-users-by-ids"
                  :> (Until 'V3
                      :> (ZLocalUser
                          :> (ZConn
                              :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                  :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'ConvNotFound
                                              :> (CanThrow 'InvalidOperation
                                                  :> (CanThrow 'InvalidTargetAccess
                                                      :> ("conversations"
                                                          :> (QualifiedCapture'
                                                                '[Description "Conversation ID"]
                                                                "cnv"
                                                                ConvId
                                                              :> ("access"
                                                                  :> (VersionedReqBody
                                                                        'V2
                                                                        '[JSON]
                                                                        ConversationAccessData
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           (UpdateResponses
                                                                              "Access unchanged"
                                                                              "Access updated"
                                                                              Event)
                                                                           (UpdateResult
                                                                              Event)))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-access"
        (Summary "Update access modes for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (From 'V3
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'InvalidTargetAccess
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("access"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationAccessData
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Access unchanged"
                                                                                 "Access updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "get-conversation-self-unqualified"
              (Summary "Get self membership properties (deprecated)"
               :> (Deprecated
                   :> (ZLocalUser
                       :> ("conversations"
                           :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                               :> ("self" :> Get '[JSON] (Maybe Member)))))))
            :<|> (Named
                    "update-conversation-self-unqualified"
                    (Summary "Update self membership properties (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/self` instead."
                             :> (CanThrow 'ConvNotFound
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (Capture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("self"
                                                     :> (ReqBody '[JSON] MemberUpdate
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              '[RespondEmpty
                                                                  200 "Update successful"]
                                                              ()))))))))))
                  :<|> (Named
                          "update-conversation-self"
                          (Summary "Update self membership properties"
                           :> (Description "**Note**: at least one field has to be provided."
                               :> (CanThrow 'ConvNotFound
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> ("conversations"
                                               :> (QualifiedCapture'
                                                     '[Description "Conversation ID"] "cnv" ConvId
                                                   :> ("self"
                                                       :> (ReqBody '[JSON] MemberUpdate
                                                           :> MultiVerb
                                                                'PUT
                                                                '[JSON]
                                                                '[RespondEmpty
                                                                    200 "Update successful"]
                                                                ())))))))))
                        :<|> Named
                               "update-conversation-protocol"
                               (Summary "Update the protocol of the conversation"
                                :> (From 'V5
                                    :> (Description
                                          "**Note**: Only proteus->mixed upgrade is supported."
                                        :> (CanThrow 'ConvNotFound
                                            :> (CanThrow 'ConvInvalidProtocolTransition
                                                :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                    :> (CanThrow 'InvalidOperation
                                                        :> (CanThrow
                                                              'MLSMigrationCriteriaNotSatisfied
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (ZLocalUser
                                                                            :> (ZConn
                                                                                :> ("conversations"
                                                                                    :> (QualifiedCapture'
                                                                                          '[Description
                                                                                              "Conversation ID"]
                                                                                          "cnv"
                                                                                          ConvId
                                                                                        :> ("protocol"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  ProtocolUpdate
                                                                                                :> MultiVerb
                                                                                                     'PUT
                                                                                                     '[JSON]
                                                                                                     ConvUpdateResponses
                                                                                                     (UpdateResult
                                                                                                        Event))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-access@v2"
        (Summary "Update access modes for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (Until 'V3
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'InvalidTargetAccess
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("access"
                                                                     :> (VersionedReqBody
                                                                           'V2
                                                                           '[JSON]
                                                                           ConversationAccessData
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Access unchanged"
                                                                                 "Access updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "update-conversation-access"
              (Summary "Update access modes for a conversation"
               :> (MakesFederatedCall 'Galley "on-conversation-updated"
                   :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                       :> (MakesFederatedCall 'Brig "get-users-by-ids"
                           :> (From 'V3
                               :> (ZLocalUser
                                   :> (ZConn
                                       :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                           :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                               :> (CanThrow 'ConvAccessDenied
                                                   :> (CanThrow 'ConvNotFound
                                                       :> (CanThrow 'InvalidOperation
                                                           :> (CanThrow 'InvalidTargetAccess
                                                               :> ("conversations"
                                                                   :> (QualifiedCapture'
                                                                         '[Description
                                                                             "Conversation ID"]
                                                                         "cnv"
                                                                         ConvId
                                                                       :> ("access"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 ConversationAccessData
                                                                               :> MultiVerb
                                                                                    'PUT
                                                                                    '[JSON]
                                                                                    (UpdateResponses
                                                                                       "Access unchanged"
                                                                                       "Access updated"
                                                                                       Event)
                                                                                    (UpdateResult
                                                                                       Event))))))))))))))))))
            :<|> (Named
                    "get-conversation-self-unqualified"
                    (Summary "Get self membership properties (deprecated)"
                     :> (Deprecated
                         :> (ZLocalUser
                             :> ("conversations"
                                 :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("self" :> Get '[JSON] (Maybe Member)))))))
                  :<|> (Named
                          "update-conversation-self-unqualified"
                          (Summary "Update self membership properties (deprecated)"
                           :> (Deprecated
                               :> (Description "Use `/conversations/:domain/:conv/self` instead."
                                   :> (CanThrow 'ConvNotFound
                                       :> (ZLocalUser
                                           :> (ZConn
                                               :> ("conversations"
                                                   :> (Capture'
                                                         '[Description "Conversation ID"]
                                                         "cnv"
                                                         ConvId
                                                       :> ("self"
                                                           :> (ReqBody '[JSON] MemberUpdate
                                                               :> MultiVerb
                                                                    'PUT
                                                                    '[JSON]
                                                                    '[RespondEmpty
                                                                        200 "Update successful"]
                                                                    ()))))))))))
                        :<|> (Named
                                "update-conversation-self"
                                (Summary "Update self membership properties"
                                 :> (Description "**Note**: at least one field has to be provided."
                                     :> (CanThrow 'ConvNotFound
                                         :> (ZLocalUser
                                             :> (ZConn
                                                 :> ("conversations"
                                                     :> (QualifiedCapture'
                                                           '[Description "Conversation ID"]
                                                           "cnv"
                                                           ConvId
                                                         :> ("self"
                                                             :> (ReqBody '[JSON] MemberUpdate
                                                                 :> MultiVerb
                                                                      'PUT
                                                                      '[JSON]
                                                                      '[RespondEmpty
                                                                          200 "Update successful"]
                                                                      ())))))))))
                              :<|> Named
                                     "update-conversation-protocol"
                                     (Summary "Update the protocol of the conversation"
                                      :> (From 'V5
                                          :> (Description
                                                "**Note**: Only proteus->mixed upgrade is supported."
                                              :> (CanThrow 'ConvNotFound
                                                  :> (CanThrow 'ConvInvalidProtocolTransition
                                                      :> (CanThrow
                                                            ('ActionDenied 'LeaveConversation)
                                                          :> (CanThrow 'InvalidOperation
                                                              :> (CanThrow
                                                                    'MLSMigrationCriteriaNotSatisfied
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> (ZLocalUser
                                                                                  :> (ZConn
                                                                                      :> ("conversations"
                                                                                          :> (QualifiedCapture'
                                                                                                '[Description
                                                                                                    "Conversation ID"]
                                                                                                "cnv"
                                                                                                ConvId
                                                                                              :> ("protocol"
                                                                                                  :> (ReqBody
                                                                                                        '[JSON]
                                                                                                        ProtocolUpdate
                                                                                                      :> MultiVerb
                                                                                                           'PUT
                                                                                                           '[JSON]
                                                                                                           ConvUpdateResponses
                                                                                                           (UpdateResult
                                                                                                              Event)))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-access" (((HasAnnotation 'Remote "galley" "on-conversation-updated",
  (HasAnnotation 'Remote "galley" "on-mls-message-sent",
   (HasAnnotation 'Remote "brig" "get-users-by-ids",
    () :: Constraint))) =>
 QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> Dict (HasAnnotation 'Remote "galley" "on-conversation-updated")
-> Dict (HasAnnotation 'Remote "galley" "on-mls-message-sent")
-> Dict (HasAnnotation 'Remote "brig" "get-users-by-ids")
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (c :: Constraint) r a. SolveCallsFed c r a => (c => r) -> a
callsFed ((QualifiedWithTag 'QLocal UserId
 -> ConnId
 -> Qualified ConvId
 -> ConversationAccessData
 -> Sem
      '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
        Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
        Error (Tagged 'ConvAccessDenied ()),
        Error (Tagged 'ConvNotFound ()),
        Error (Tagged 'InvalidOperation ()),
        Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
        Error InvalidInput, Error InternalError, Error FederationError,
        Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
        Final IO]
      (UpdateResult Event))
-> QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall x a. ToHasAnnotations x => a -> a
exposeAnnotations QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem
     '[Error (Tagged ('ActionDenied 'ModifyConversationAccess) ()),
       Error (Tagged ('ActionDenied 'RemoveConversationMember) ()),
       Error (Tagged 'ConvAccessDenied ()),
       Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'InvalidTargetAccess ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
Members UpdateConversationAccessEffects r =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ConversationAccessData
-> Sem r (UpdateResult Event)
updateConversationAccess))
    API
  (Named
     "update-conversation-access"
     (Summary "Update access modes for a conversation"
      :> (MakesFederatedCall 'Galley "on-conversation-updated"
          :> (MakesFederatedCall 'Galley "on-mls-message-sent"
              :> (MakesFederatedCall 'Brig "get-users-by-ids"
                  :> (From 'V3
                      :> (ZLocalUser
                          :> (ZConn
                              :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                  :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                      :> (CanThrow 'ConvAccessDenied
                                          :> (CanThrow 'ConvNotFound
                                              :> (CanThrow 'InvalidOperation
                                                  :> (CanThrow 'InvalidTargetAccess
                                                      :> ("conversations"
                                                          :> (QualifiedCapture'
                                                                '[Description "Conversation ID"]
                                                                "cnv"
                                                                ConvId
                                                              :> ("access"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        ConversationAccessData
                                                                      :> MultiVerb
                                                                           'PUT
                                                                           '[JSON]
                                                                           (UpdateResponses
                                                                              "Access unchanged"
                                                                              "Access updated"
                                                                              Event)
                                                                           (UpdateResult
                                                                              Event)))))))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "get-conversation-self-unqualified"
        (Summary "Get self membership properties (deprecated)"
         :> (Deprecated
             :> (ZLocalUser
                 :> ("conversations"
                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                         :> ("self" :> Get '[JSON] (Maybe Member)))))))
      :<|> (Named
              "update-conversation-self-unqualified"
              (Summary "Update self membership properties (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/self` instead."
                       :> (CanThrow 'ConvNotFound
                           :> (ZLocalUser
                               :> (ZConn
                                   :> ("conversations"
                                       :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("self"
                                               :> (ReqBody '[JSON] MemberUpdate
                                                   :> MultiVerb
                                                        'PUT
                                                        '[JSON]
                                                        '[RespondEmpty 200 "Update successful"]
                                                        ()))))))))))
            :<|> (Named
                    "update-conversation-self"
                    (Summary "Update self membership properties"
                     :> (Description "**Note**: at least one field has to be provided."
                         :> (CanThrow 'ConvNotFound
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> ("conversations"
                                         :> (QualifiedCapture'
                                               '[Description "Conversation ID"] "cnv" ConvId
                                             :> ("self"
                                                 :> (ReqBody '[JSON] MemberUpdate
                                                     :> MultiVerb
                                                          'PUT
                                                          '[JSON]
                                                          '[RespondEmpty 200 "Update successful"]
                                                          ())))))))))
                  :<|> Named
                         "update-conversation-protocol"
                         (Summary "Update the protocol of the conversation"
                          :> (From 'V5
                              :> (Description
                                    "**Note**: Only proteus->mixed upgrade is supported."
                                  :> (CanThrow 'ConvNotFound
                                      :> (CanThrow 'ConvInvalidProtocolTransition
                                          :> (CanThrow ('ActionDenied 'LeaveConversation)
                                              :> (CanThrow 'InvalidOperation
                                                  :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (ZLocalUser
                                                                      :> (ZConn
                                                                          :> ("conversations"
                                                                              :> (QualifiedCapture'
                                                                                    '[Description
                                                                                        "Conversation ID"]
                                                                                    "cnv"
                                                                                    ConvId
                                                                                  :> ("protocol"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            ProtocolUpdate
                                                                                          :> MultiVerb
                                                                                               'PUT
                                                                                               '[JSON]
                                                                                               ConvUpdateResponses
                                                                                               (UpdateResult
                                                                                                  Event)))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-access"
        (Summary "Update access modes for a conversation"
         :> (MakesFederatedCall 'Galley "on-conversation-updated"
             :> (MakesFederatedCall 'Galley "on-mls-message-sent"
                 :> (MakesFederatedCall 'Brig "get-users-by-ids"
                     :> (From 'V3
                         :> (ZLocalUser
                             :> (ZConn
                                 :> (CanThrow ('ActionDenied 'ModifyConversationAccess)
                                     :> (CanThrow ('ActionDenied 'RemoveConversationMember)
                                         :> (CanThrow 'ConvAccessDenied
                                             :> (CanThrow 'ConvNotFound
                                                 :> (CanThrow 'InvalidOperation
                                                     :> (CanThrow 'InvalidTargetAccess
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("access"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           ConversationAccessData
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              (UpdateResponses
                                                                                 "Access unchanged"
                                                                                 "Access updated"
                                                                                 Event)
                                                                              (UpdateResult
                                                                                 Event))))))))))))))))))
      :<|> (Named
              "get-conversation-self-unqualified"
              (Summary "Get self membership properties (deprecated)"
               :> (Deprecated
                   :> (ZLocalUser
                       :> ("conversations"
                           :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                               :> ("self" :> Get '[JSON] (Maybe Member)))))))
            :<|> (Named
                    "update-conversation-self-unqualified"
                    (Summary "Update self membership properties (deprecated)"
                     :> (Deprecated
                         :> (Description "Use `/conversations/:domain/:conv/self` instead."
                             :> (CanThrow 'ConvNotFound
                                 :> (ZLocalUser
                                     :> (ZConn
                                         :> ("conversations"
                                             :> (Capture'
                                                   '[Description "Conversation ID"] "cnv" ConvId
                                                 :> ("self"
                                                     :> (ReqBody '[JSON] MemberUpdate
                                                         :> MultiVerb
                                                              'PUT
                                                              '[JSON]
                                                              '[RespondEmpty
                                                                  200 "Update successful"]
                                                              ()))))))))))
                  :<|> (Named
                          "update-conversation-self"
                          (Summary "Update self membership properties"
                           :> (Description "**Note**: at least one field has to be provided."
                               :> (CanThrow 'ConvNotFound
                                   :> (ZLocalUser
                                       :> (ZConn
                                           :> ("conversations"
                                               :> (QualifiedCapture'
                                                     '[Description "Conversation ID"] "cnv" ConvId
                                                   :> ("self"
                                                       :> (ReqBody '[JSON] MemberUpdate
                                                           :> MultiVerb
                                                                'PUT
                                                                '[JSON]
                                                                '[RespondEmpty
                                                                    200 "Update successful"]
                                                                ())))))))))
                        :<|> Named
                               "update-conversation-protocol"
                               (Summary "Update the protocol of the conversation"
                                :> (From 'V5
                                    :> (Description
                                          "**Note**: Only proteus->mixed upgrade is supported."
                                        :> (CanThrow 'ConvNotFound
                                            :> (CanThrow 'ConvInvalidProtocolTransition
                                                :> (CanThrow ('ActionDenied 'LeaveConversation)
                                                    :> (CanThrow 'InvalidOperation
                                                        :> (CanThrow
                                                              'MLSMigrationCriteriaNotSatisfied
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> (ZLocalUser
                                                                            :> (ZConn
                                                                                :> ("conversations"
                                                                                    :> (QualifiedCapture'
                                                                                          '[Description
                                                                                              "Conversation ID"]
                                                                                          "cnv"
                                                                                          ConvId
                                                                                        :> ("protocol"
                                                                                            :> (ReqBody
                                                                                                  '[JSON]
                                                                                                  ProtocolUpdate
                                                                                                :> MultiVerb
                                                                                                     'PUT
                                                                                                     '[JSON]
                                                                                                     ConvUpdateResponses
                                                                                                     (UpdateResult
                                                                                                        Event))))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"get-conversation-self-unqualified" ServerT
  (Summary "Get self membership properties (deprecated)"
   :> (Deprecated
       :> (ZLocalUser
           :> ("conversations"
               :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                   :> ("self" :> Get '[JSON] (Maybe Member)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Get self membership properties (deprecated)"
            :> (Deprecated
                :> (ZLocalUser
                    :> ("conversations"
                        :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                            :> ("self" :> Get '[JSON] (Maybe Member))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConvId
-> Sem
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (Maybe Member)
forall (r :: EffectRow).
(Member ConversationStore r, Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId -> ConvId -> Sem r (Maybe Member)
getLocalSelf
    API
  (Named
     "get-conversation-self-unqualified"
     (Summary "Get self membership properties (deprecated)"
      :> (Deprecated
          :> (ZLocalUser
              :> ("conversations"
                  :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                      :> ("self" :> Get '[JSON] (Maybe Member))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-self-unqualified"
        (Summary "Update self membership properties (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/self` instead."
                 :> (CanThrow 'ConvNotFound
                     :> (ZLocalUser
                         :> (ZConn
                             :> ("conversations"
                                 :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("self"
                                         :> (ReqBody '[JSON] MemberUpdate
                                             :> MultiVerb
                                                  'PUT
                                                  '[JSON]
                                                  '[RespondEmpty 200 "Update successful"]
                                                  ()))))))))))
      :<|> (Named
              "update-conversation-self"
              (Summary "Update self membership properties"
               :> (Description "**Note**: at least one field has to be provided."
                   :> (CanThrow 'ConvNotFound
                       :> (ZLocalUser
                           :> (ZConn
                               :> ("conversations"
                                   :> (QualifiedCapture'
                                         '[Description "Conversation ID"] "cnv" ConvId
                                       :> ("self"
                                           :> (ReqBody '[JSON] MemberUpdate
                                               :> MultiVerb
                                                    'PUT
                                                    '[JSON]
                                                    '[RespondEmpty 200 "Update successful"]
                                                    ())))))))))
            :<|> Named
                   "update-conversation-protocol"
                   (Summary "Update the protocol of the conversation"
                    :> (From 'V5
                        :> (Description
                              "**Note**: Only proteus->mixed upgrade is supported."
                            :> (CanThrow 'ConvNotFound
                                :> (CanThrow 'ConvInvalidProtocolTransition
                                    :> (CanThrow ('ActionDenied 'LeaveConversation)
                                        :> (CanThrow 'InvalidOperation
                                            :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (ZLocalUser
                                                                :> (ZConn
                                                                    :> ("conversations"
                                                                        :> (QualifiedCapture'
                                                                              '[Description
                                                                                  "Conversation ID"]
                                                                              "cnv"
                                                                              ConvId
                                                                            :> ("protocol"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      ProtocolUpdate
                                                                                    :> MultiVerb
                                                                                         'PUT
                                                                                         '[JSON]
                                                                                         ConvUpdateResponses
                                                                                         (UpdateResult
                                                                                            Event))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "get-conversation-self-unqualified"
        (Summary "Get self membership properties (deprecated)"
         :> (Deprecated
             :> (ZLocalUser
                 :> ("conversations"
                     :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                         :> ("self" :> Get '[JSON] (Maybe Member)))))))
      :<|> (Named
              "update-conversation-self-unqualified"
              (Summary "Update self membership properties (deprecated)"
               :> (Deprecated
                   :> (Description "Use `/conversations/:domain/:conv/self` instead."
                       :> (CanThrow 'ConvNotFound
                           :> (ZLocalUser
                               :> (ZConn
                                   :> ("conversations"
                                       :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                           :> ("self"
                                               :> (ReqBody '[JSON] MemberUpdate
                                                   :> MultiVerb
                                                        'PUT
                                                        '[JSON]
                                                        '[RespondEmpty 200 "Update successful"]
                                                        ()))))))))))
            :<|> (Named
                    "update-conversation-self"
                    (Summary "Update self membership properties"
                     :> (Description "**Note**: at least one field has to be provided."
                         :> (CanThrow 'ConvNotFound
                             :> (ZLocalUser
                                 :> (ZConn
                                     :> ("conversations"
                                         :> (QualifiedCapture'
                                               '[Description "Conversation ID"] "cnv" ConvId
                                             :> ("self"
                                                 :> (ReqBody '[JSON] MemberUpdate
                                                     :> MultiVerb
                                                          'PUT
                                                          '[JSON]
                                                          '[RespondEmpty 200 "Update successful"]
                                                          ())))))))))
                  :<|> Named
                         "update-conversation-protocol"
                         (Summary "Update the protocol of the conversation"
                          :> (From 'V5
                              :> (Description
                                    "**Note**: Only proteus->mixed upgrade is supported."
                                  :> (CanThrow 'ConvNotFound
                                      :> (CanThrow 'ConvInvalidProtocolTransition
                                          :> (CanThrow ('ActionDenied 'LeaveConversation)
                                              :> (CanThrow 'InvalidOperation
                                                  :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> (ZLocalUser
                                                                      :> (ZConn
                                                                          :> ("conversations"
                                                                              :> (QualifiedCapture'
                                                                                    '[Description
                                                                                        "Conversation ID"]
                                                                                    "cnv"
                                                                                    ConvId
                                                                                  :> ("protocol"
                                                                                      :> (ReqBody
                                                                                            '[JSON]
                                                                                            ProtocolUpdate
                                                                                          :> MultiVerb
                                                                                               'PUT
                                                                                               '[JSON]
                                                                                               ConvUpdateResponses
                                                                                               (UpdateResult
                                                                                                  Event)))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-self-unqualified" ServerT
  (Summary "Update self membership properties (deprecated)"
   :> (Deprecated
       :> (Description "Use `/conversations/:domain/:conv/self` instead."
           :> (CanThrow 'ConvNotFound
               :> (ZLocalUser
                   :> (ZConn
                       :> ("conversations"
                           :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                               :> ("self"
                                   :> (ReqBody '[JSON] MemberUpdate
                                       :> MultiVerb
                                            'PUT
                                            '[JSON]
                                            '[RespondEmpty 200 "Update successful"]
                                            ()))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Update self membership properties (deprecated)"
            :> (Deprecated
                :> (Description "Use `/conversations/:domain/:conv/self` instead."
                    :> (CanThrow 'ConvNotFound
                        :> (ZLocalUser
                            :> (ZConn
                                :> ("conversations"
                                    :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                        :> ("self"
                                            :> (ReqBody '[JSON] MemberUpdate
                                                :> MultiVerb
                                                     'PUT
                                                     '[JSON]
                                                     '[RespondEmpty 200 "Update successful"]
                                                     ())))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConnId
-> ConvId
-> MemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> ConvId -> MemberUpdate -> Sem r ()
updateUnqualifiedSelfMember
    API
  (Named
     "update-conversation-self-unqualified"
     (Summary "Update self membership properties (deprecated)"
      :> (Deprecated
          :> (Description "Use `/conversations/:domain/:conv/self` instead."
              :> (CanThrow 'ConvNotFound
                  :> (ZLocalUser
                      :> (ZConn
                          :> ("conversations"
                              :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                  :> ("self"
                                      :> (ReqBody '[JSON] MemberUpdate
                                          :> MultiVerb
                                               'PUT
                                               '[JSON]
                                               '[RespondEmpty 200 "Update successful"]
                                               ())))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-self"
        (Summary "Update self membership properties"
         :> (Description "**Note**: at least one field has to be provided."
             :> (CanThrow 'ConvNotFound
                 :> (ZLocalUser
                     :> (ZConn
                         :> ("conversations"
                             :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                 :> ("self"
                                     :> (ReqBody '[JSON] MemberUpdate
                                         :> MultiVerb
                                              'PUT
                                              '[JSON]
                                              '[RespondEmpty 200 "Update successful"]
                                              ())))))))))
      :<|> Named
             "update-conversation-protocol"
             (Summary "Update the protocol of the conversation"
              :> (From 'V5
                  :> (Description
                        "**Note**: Only proteus->mixed upgrade is supported."
                      :> (CanThrow 'ConvNotFound
                          :> (CanThrow 'ConvInvalidProtocolTransition
                              :> (CanThrow ('ActionDenied 'LeaveConversation)
                                  :> (CanThrow 'InvalidOperation
                                      :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (ZLocalUser
                                                          :> (ZConn
                                                              :> ("conversations"
                                                                  :> (QualifiedCapture'
                                                                        '[Description
                                                                            "Conversation ID"]
                                                                        "cnv"
                                                                        ConvId
                                                                      :> ("protocol"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                ProtocolUpdate
                                                                              :> MultiVerb
                                                                                   'PUT
                                                                                   '[JSON]
                                                                                   ConvUpdateResponses
                                                                                   (UpdateResult
                                                                                      Event)))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-self-unqualified"
        (Summary "Update self membership properties (deprecated)"
         :> (Deprecated
             :> (Description "Use `/conversations/:domain/:conv/self` instead."
                 :> (CanThrow 'ConvNotFound
                     :> (ZLocalUser
                         :> (ZConn
                             :> ("conversations"
                                 :> (Capture' '[Description "Conversation ID"] "cnv" ConvId
                                     :> ("self"
                                         :> (ReqBody '[JSON] MemberUpdate
                                             :> MultiVerb
                                                  'PUT
                                                  '[JSON]
                                                  '[RespondEmpty 200 "Update successful"]
                                                  ()))))))))))
      :<|> (Named
              "update-conversation-self"
              (Summary "Update self membership properties"
               :> (Description "**Note**: at least one field has to be provided."
                   :> (CanThrow 'ConvNotFound
                       :> (ZLocalUser
                           :> (ZConn
                               :> ("conversations"
                                   :> (QualifiedCapture'
                                         '[Description "Conversation ID"] "cnv" ConvId
                                       :> ("self"
                                           :> (ReqBody '[JSON] MemberUpdate
                                               :> MultiVerb
                                                    'PUT
                                                    '[JSON]
                                                    '[RespondEmpty 200 "Update successful"]
                                                    ())))))))))
            :<|> Named
                   "update-conversation-protocol"
                   (Summary "Update the protocol of the conversation"
                    :> (From 'V5
                        :> (Description
                              "**Note**: Only proteus->mixed upgrade is supported."
                            :> (CanThrow 'ConvNotFound
                                :> (CanThrow 'ConvInvalidProtocolTransition
                                    :> (CanThrow ('ActionDenied 'LeaveConversation)
                                        :> (CanThrow 'InvalidOperation
                                            :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'TeamNotFound
                                                            :> (ZLocalUser
                                                                :> (ZConn
                                                                    :> ("conversations"
                                                                        :> (QualifiedCapture'
                                                                              '[Description
                                                                                  "Conversation ID"]
                                                                              "cnv"
                                                                              ConvId
                                                                            :> ("protocol"
                                                                                :> (ReqBody
                                                                                      '[JSON]
                                                                                      ProtocolUpdate
                                                                                    :> MultiVerb
                                                                                         'PUT
                                                                                         '[JSON]
                                                                                         ConvUpdateResponses
                                                                                         (UpdateResult
                                                                                            Event))))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-self" ServerT
  (Summary "Update self membership properties"
   :> (Description "**Note**: at least one field has to be provided."
       :> (CanThrow 'ConvNotFound
           :> (ZLocalUser
               :> (ZConn
                   :> ("conversations"
                       :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                           :> ("self"
                               :> (ReqBody '[JSON] MemberUpdate
                                   :> MultiVerb
                                        'PUT
                                        '[JSON]
                                        '[RespondEmpty 200 "Update successful"]
                                        ())))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Update self membership properties"
            :> (Description "**Note**: at least one field has to be provided."
                :> (CanThrow 'ConvNotFound
                    :> (ZLocalUser
                        :> (ZConn
                            :> ("conversations"
                                :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                    :> ("self"
                                        :> (ReqBody '[JSON] MemberUpdate
                                            :> MultiVerb
                                                 'PUT
                                                 '[JSON]
                                                 '[RespondEmpty 200 "Update successful"]
                                                 ()))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> MemberUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     ()
forall (r :: EffectRow).
(Member ConversationStore r,
 Member (Error (Tagged 'ConvNotFound ())) r,
 Member ExternalAccess r, Member NotificationSubsystem r,
 Member (Input UTCTime) r, Member MemberStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId -> Qualified ConvId -> MemberUpdate -> Sem r ()
updateSelfMember
    API
  (Named
     "update-conversation-self"
     (Summary "Update self membership properties"
      :> (Description "**Note**: at least one field has to be provided."
          :> (CanThrow 'ConvNotFound
              :> (ZLocalUser
                  :> (ZConn
                      :> ("conversations"
                          :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                              :> ("self"
                                  :> (ReqBody '[JSON] MemberUpdate
                                      :> MultiVerb
                                           'PUT
                                           '[JSON]
                                           '[RespondEmpty 200 "Update successful"]
                                           ()))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        "update-conversation-protocol"
        (Summary "Update the protocol of the conversation"
         :> (From 'V5
             :> (Description
                   "**Note**: Only proteus->mixed upgrade is supported."
                 :> (CanThrow 'ConvNotFound
                     :> (CanThrow 'ConvInvalidProtocolTransition
                         :> (CanThrow ('ActionDenied 'LeaveConversation)
                             :> (CanThrow 'InvalidOperation
                                 :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'TeamNotFound
                                                 :> (ZLocalUser
                                                     :> (ZConn
                                                         :> ("conversations"
                                                             :> (QualifiedCapture'
                                                                   '[Description "Conversation ID"]
                                                                   "cnv"
                                                                   ConvId
                                                                 :> ("protocol"
                                                                     :> (ReqBody
                                                                           '[JSON] ProtocolUpdate
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              ConvUpdateResponses
                                                                              (UpdateResult
                                                                                 Event)))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
-> API
     (Named
        "update-conversation-self"
        (Summary "Update self membership properties"
         :> (Description "**Note**: at least one field has to be provided."
             :> (CanThrow 'ConvNotFound
                 :> (ZLocalUser
                     :> (ZConn
                         :> ("conversations"
                             :> (QualifiedCapture' '[Description "Conversation ID"] "cnv" ConvId
                                 :> ("self"
                                     :> (ReqBody '[JSON] MemberUpdate
                                         :> MultiVerb
                                              'PUT
                                              '[JSON]
                                              '[RespondEmpty 200 "Update successful"]
                                              ())))))))))
      :<|> Named
             "update-conversation-protocol"
             (Summary "Update the protocol of the conversation"
              :> (From 'V5
                  :> (Description
                        "**Note**: Only proteus->mixed upgrade is supported."
                      :> (CanThrow 'ConvNotFound
                          :> (CanThrow 'ConvInvalidProtocolTransition
                              :> (CanThrow ('ActionDenied 'LeaveConversation)
                                  :> (CanThrow 'InvalidOperation
                                      :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'TeamNotFound
                                                      :> (ZLocalUser
                                                          :> (ZConn
                                                              :> ("conversations"
                                                                  :> (QualifiedCapture'
                                                                        '[Description
                                                                            "Conversation ID"]
                                                                        "cnv"
                                                                        ConvId
                                                                      :> ("protocol"
                                                                          :> (ReqBody
                                                                                '[JSON]
                                                                                ProtocolUpdate
                                                                              :> MultiVerb
                                                                                   'PUT
                                                                                   '[JSON]
                                                                                   ConvUpdateResponses
                                                                                   (UpdateResult
                                                                                      Event)))))))))))))))))))
     '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
forall api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> forall {k} (name :: k) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
forall (name :: Symbol) (r0 :: EffectRow) api.
(HasServer api '[Domain],
 ServerEffects (DeclaredErrorEffects api) r0) =>
ServerT api (Sem (Append (DeclaredErrorEffects api) r0))
-> API (Named name api) r0
mkNamedAPI @"update-conversation-protocol" ServerT
  (Summary "Update the protocol of the conversation"
   :> (From 'V5
       :> (Description
             "**Note**: Only proteus->mixed upgrade is supported."
           :> (CanThrow 'ConvNotFound
               :> (CanThrow 'ConvInvalidProtocolTransition
                   :> (CanThrow ('ActionDenied 'LeaveConversation)
                       :> (CanThrow 'InvalidOperation
                           :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'TeamNotFound
                                           :> (ZLocalUser
                                               :> (ZConn
                                                   :> ("conversations"
                                                       :> (QualifiedCapture'
                                                             '[Description "Conversation ID"]
                                                             "cnv"
                                                             ConvId
                                                           :> ("protocol"
                                                               :> (ReqBody '[JSON] ProtocolUpdate
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        ConvUpdateResponses
                                                                        (UpdateResult
                                                                           Event))))))))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Update the protocol of the conversation"
            :> (From 'V5
                :> (Description
                      "**Note**: Only proteus->mixed upgrade is supported."
                    :> (CanThrow 'ConvNotFound
                        :> (CanThrow 'ConvInvalidProtocolTransition
                            :> (CanThrow ('ActionDenied 'LeaveConversation)
                                :> (CanThrow 'InvalidOperation
                                    :> (CanThrow 'MLSMigrationCriteriaNotSatisfied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> (ZLocalUser
                                                        :> (ZConn
                                                            :> ("conversations"
                                                                :> (QualifiedCapture'
                                                                      '[Description
                                                                          "Conversation ID"]
                                                                      "cnv"
                                                                      ConvId
                                                                    :> ("protocol"
                                                                        :> (ReqBody
                                                                              '[JSON] ProtocolUpdate
                                                                            :> MultiVerb
                                                                                 'PUT
                                                                                 '[JSON]
                                                                                 ConvUpdateResponses
                                                                                 (UpdateResult
                                                                                    Event)))))))))))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ProtocolUpdate
-> Sem
     '[Error (Tagged 'ConvNotFound ()),
       Error (Tagged 'ConvInvalidProtocolTransition ()),
       Error (Tagged ('ActionDenied 'LeaveConversation) ()),
       Error (Tagged 'InvalidOperation ()),
       Error (Tagged 'MLSMigrationCriteriaNotSatisfied ()),
       Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (UpdateResult Event)
forall (r :: EffectRow).
(Member (Error (Tagged 'ConvNotFound ())) r,
 Member (Error (Tagged 'ConvInvalidProtocolTransition ())) r,
 Member (Error (Tagged ('ActionDenied 'LeaveConversation) ())) r,
 Member (Error (Tagged 'InvalidOperation ())) r,
 Member (Error FederationError) r,
 Member (Error (Tagged 'MLSMigrationCriteriaNotSatisfied ())) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error InternalError) r, Member (Input UTCTime) r,
 Member (Input Env) r, Member (Input (Local ())) r,
 Member (Input Opts) r, Member BackendNotificationQueueAccess r,
 Member BrigAccess r, Member ConversationStore r,
 Member MemberStore r, Member (Logger (Msg -> Msg)) r,
 Member NotificationSubsystem r, Member ExternalAccess r,
 Member FederatorAccess r, Member Random r, Member ProposalStore r,
 Member SubConversationStore r, Member TeamFeatureStore r) =>
QualifiedWithTag 'QLocal UserId
-> ConnId
-> Qualified ConvId
-> ProtocolUpdate
-> Sem r (UpdateResult Event)
updateConversationProtocolWithLocalUser